aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r--lib/stdlib/src/beam_lib.erl19
-rw-r--r--lib/stdlib/src/c.erl2
-rw-r--r--lib/stdlib/src/epp.erl9
-rw-r--r--lib/stdlib/src/erl_eval.erl10
-rw-r--r--lib/stdlib/src/erl_internal.erl2
-rw-r--r--lib/stdlib/src/error_logger_tty_h.erl69
-rw-r--r--lib/stdlib/src/escript.erl2
-rw-r--r--lib/stdlib/src/eval_bits.erl47
-rw-r--r--lib/stdlib/src/gen_event.erl8
-rw-r--r--lib/stdlib/src/gen_fsm.erl6
-rw-r--r--lib/stdlib/src/gen_server.erl6
-rw-r--r--lib/stdlib/src/lib.erl46
-rw-r--r--lib/stdlib/src/otp_internal.erl38
-rw-r--r--lib/stdlib/src/qlc.erl7
-rw-r--r--lib/stdlib/src/re.erl16
-rw-r--r--lib/stdlib/src/shell.erl2
-rw-r--r--lib/stdlib/src/supervisor.erl3
-rw-r--r--lib/stdlib/src/unicode.erl12
18 files changed, 172 insertions, 132 deletions
diff --git a/lib/stdlib/src/beam_lib.erl b/lib/stdlib/src/beam_lib.erl
index d9c645d787..9077e59fdc 100644
--- a/lib/stdlib/src/beam_lib.erl
+++ b/lib/stdlib/src/beam_lib.erl
@@ -224,7 +224,7 @@ version(File) ->
MD5 :: binary().
md5(File) ->
- case catch read_significant_chunks(File) of
+ case catch read_significant_chunks(File, md5_chunks()) of
{ok, {Module, Chunks0}} ->
Chunks = filter_funtab(Chunks0),
{ok, {Module, erlang:md5([C || {_Id, C} <- Chunks])}};
@@ -395,7 +395,7 @@ strip_fils(Files) ->
%% -> {ok, {Mod, FileName}} | {ok, {Mod, binary()}} | throw(Error)
strip_file(File) ->
- {ok, {Mod, Chunks}} = read_significant_chunks(File),
+ {ok, {Mod, Chunks}} = read_significant_chunks(File, significant_chunks()),
{ok, Stripped0} = build_module(Chunks),
Stripped = compress(Stripped0),
case File of
@@ -453,8 +453,8 @@ is_useless_chunk("CInf") -> true;
is_useless_chunk(_) -> false.
%% -> {ok, {Module, Chunks}} | throw(Error)
-read_significant_chunks(File) ->
- case read_chunk_data(File, significant_chunks(), [allow_missing_chunks]) of
+read_significant_chunks(File, ChunkList) ->
+ case read_chunk_data(File, ChunkList, [allow_missing_chunks]) of
{ok, {Module, Chunks0}} ->
Mandatory = mandatory_chunks(),
Chunks = filter_significant_chunks(Chunks0, Mandatory, File, Module),
@@ -835,12 +835,15 @@ file_error(FileName, {error, Reason}) ->
error(Reason) ->
throw({error, ?MODULE, Reason}).
-
-%% The following chunks are significant when calculating the MD5 for a module,
-%% and also the modules that must be retained when stripping a file.
-%% They are listed in the order that they should be MD5:ed.
+%% The following chunks must be kept when stripping a BEAM file.
significant_chunks() ->
+ ["Line" | md5_chunks()].
+
+%% The following chunks are significant when calculating the MD5
+%% for a module. They are listed in the order that they should be MD5:ed.
+
+md5_chunks() ->
["Atom", "Code", "StrT", "ImpT", "ExpT", "FunT", "LitT"].
%% The following chunks are mandatory in every Beam file.
diff --git a/lib/stdlib/src/c.erl b/lib/stdlib/src/c.erl
index febfdd6285..a920921a5e 100644
--- a/lib/stdlib/src/c.erl
+++ b/lib/stdlib/src/c.erl
@@ -797,7 +797,7 @@ appcall(App, M, F, Args) ->
catch
error:undef ->
case erlang:get_stacktrace() of
- [{M,F,Args}|_] ->
+ [{M,F,Args,_}|_] ->
Arity = length(Args),
io:format("Call to ~w:~w/~w in application ~w failed.\n",
[M,F,Arity,App]);
diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl
index d804c1dee5..230a4a0612 100644
--- a/lib/stdlib/src/epp.erl
+++ b/lib/stdlib/src/epp.erl
@@ -684,7 +684,7 @@ scan_include_lib([{'(',_Llp},{string,_Lf,NewName0},{')',_Lrp},{dot,_Ld}],
{error,_E1} ->
case catch find_lib_dir(NewName) of
{LibDir, Rest} when is_list(LibDir) ->
- LibName = filename:join([LibDir | Rest]),
+ LibName = fname_join([LibDir | Rest]),
case file:open(LibName, [read]) of
{ok,NewF} ->
ExtraPath = [filename:dirname(LibName)],
@@ -1154,7 +1154,12 @@ expand_var1(NewName) ->
[[$$ | Var] | Rest] = filename:split(NewName),
Value = os:getenv(Var),
true = Value =/= false,
- {ok, filename:join([Value | Rest])}.
+ {ok, fname_join([Value | Rest])}.
+
+fname_join(["." | [_|_]=Rest]) ->
+ fname_join(Rest);
+fname_join(Components) ->
+ filename:join(Components).
%% The line only. (Other tokens may have the column and text as well...)
loc_attr(Line) when is_integer(Line) ->
diff --git a/lib/stdlib/src/erl_eval.erl b/lib/stdlib/src/erl_eval.erl
index 515ea2ebb7..4f4fa16040 100644
--- a/lib/stdlib/src/erl_eval.erl
+++ b/lib/stdlib/src/erl_eval.erl
@@ -621,7 +621,7 @@ eval_generate(Term, _P, _Bs0, _Lf, _Ef, _CompFun, _Acc) ->
erlang:raise(error, {bad_generator,Term}, stacktrace()).
eval_b_generate(<<_/bitstring>>=Bin, P, Bs0, Lf, Ef, CompFun, Acc) ->
- Mfun = fun(L, R, Bs) -> match1(L, R, Bs, Bs0) end,
+ Mfun = match_fun(Bs0),
Efun = fun(Exp, Bs) -> expr(Exp, Bs, Lf, Ef, none) end,
case eval_bits:bin_gen(P, Bin, new_bindings(), Bs0, Mfun, Efun) of
{match, Rest, Bs1} ->
@@ -1024,7 +1024,7 @@ match1({tuple,_,_}, _, _Bs, _BBs) ->
throw(nomatch);
match1({bin, _, Fs}, <<_/bitstring>>=B, Bs0, BBs) ->
eval_bits:match_bits(Fs, B, Bs0, BBs,
- fun(L, R, Bs) -> match1(L, R, Bs, BBs) end,
+ match_fun(BBs),
fun(E, Bs) -> expr(E, Bs, none, none, none) end);
match1({bin,_,_}, _, _Bs, _BBs) ->
throw(nomatch);
@@ -1053,6 +1053,12 @@ match1({op,Line,Op,L,R}, Term, Bs, BBs) ->
match1(_, _, _Bs, _BBs) ->
throw(invalid).
+match_fun(BBs) ->
+ fun(match, {L,R,Bs}) -> match1(L, R, Bs, BBs);
+ (binding, {Name,Bs}) -> binding(Name, Bs);
+ (add_binding, {Name,Val,Bs}) -> add_binding(Name, Val, Bs)
+ end.
+
match_tuple([E|Es], Tuple, I, Bs0, BBs) ->
{match,Bs} = match1(E, element(I, Tuple), Bs0, BBs),
match_tuple(Es, Tuple, I+1, Bs, BBs);
diff --git a/lib/stdlib/src/erl_internal.erl b/lib/stdlib/src/erl_internal.erl
index 3073fc0fb5..cd3b531d10 100644
--- a/lib/stdlib/src/erl_internal.erl
+++ b/lib/stdlib/src/erl_internal.erl
@@ -264,7 +264,6 @@ bif(bitstring_to_list, 1) -> true;
bif(byte_size, 1) -> true;
bif(check_old_code, 1) -> true;
bif(check_process_code, 2) -> true;
-bif(concat_binary, 1) -> true;
bif(date, 0) -> true;
bif(delete_module, 1) -> true;
bif(demonitor, 1) -> true;
@@ -406,7 +405,6 @@ old_bif(bit_size, 1) -> true;
old_bif(bitstring_to_list, 1) -> true;
old_bif(byte_size, 1) -> true;
old_bif(check_process_code, 2) -> true;
-old_bif(concat_binary, 1) -> true;
old_bif(date, 0) -> true;
old_bif(delete_module, 1) -> true;
old_bif(disconnect_node, 1) -> true;
diff --git a/lib/stdlib/src/error_logger_tty_h.erl b/lib/stdlib/src/error_logger_tty_h.erl
index 435e57aa0e..fa13fbb2bd 100644
--- a/lib/stdlib/src/error_logger_tty_h.erl
+++ b/lib/stdlib/src/error_logger_tty_h.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2011. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -34,10 +34,12 @@
handle_event/2, handle_call/2, handle_info/2,
terminate/2, code_change/3]).
+-export([write_event/2]).
+
%% This one is used when we takeover from the simple error_logger.
init({[], {error_logger, Buf}}) ->
User = set_group_leader(),
- write_events(Buf),
+ write_events(Buf,io),
{ok, {User, error_logger}};
%% This one is used if someone took over from us, and now wants to
%% go back.
@@ -52,7 +54,7 @@ init([]) ->
handle_event({_Type, GL, _Msg}, State) when node(GL) =/= node() ->
{ok, State};
handle_event(Event, State) ->
- write_event(tag_event(Event)),
+ write_event(tag_event(Event),io),
{ok, State}.
handle_info({'EXIT', User, _Reason}, {User, PrevHandler}) ->
@@ -64,10 +66,10 @@ handle_info({'EXIT', User, _Reason}, {User, PrevHandler}) ->
PrevHandler, go_back}
end;
handle_info({emulator, GL, Chars}, State) when node(GL) == node() ->
- write_event(tag_event({emulator, GL, Chars})),
+ write_event(tag_event({emulator, GL, Chars}),io),
{ok, State};
handle_info({emulator, noproc, Chars}, State) ->
- write_event(tag_event({emulator, noproc, Chars})),
+ write_event(tag_event({emulator, noproc, Chars}),io),
{ok, State};
handle_info(_, State) ->
{ok, State}.
@@ -97,65 +99,65 @@ set_group_leader() ->
tag_event(Event) ->
{erlang:localtime(), Event}.
-write_events(Events) -> write_events1(lists:reverse(Events)).
+write_events(Events,IOMod) -> write_events1(lists:reverse(Events),IOMod).
-write_events1([Event|Es]) ->
- write_event(Event),
- write_events1(Es);
-write_events1([]) ->
+write_events1([Event|Es],IOMod) ->
+ write_event(Event,IOMod),
+ write_events1(Es,IOMod);
+write_events1([],_IOMod) ->
ok.
-write_event({Time, {error, _GL, {Pid, Format, Args}}}) ->
+write_event({Time, {error, _GL, {Pid, Format, Args}}},IOMod) ->
T = write_time(maybe_utc(Time)),
case catch io_lib:format(add_node(Format,Pid), Args) of
S when is_list(S) ->
- format(T ++ S);
+ format(IOMod, T ++ S);
_ ->
F = add_node("ERROR: ~p - ~p~n", Pid),
- format(T ++ F, [Format,Args])
+ format(IOMod, T ++ F, [Format,Args])
end;
-write_event({Time, {emulator, _GL, Chars}}) ->
+write_event({Time, {emulator, _GL, Chars}},IOMod) ->
T = write_time(maybe_utc(Time)),
case catch io_lib:format(Chars, []) of
S when is_list(S) ->
- format(T ++ S);
+ format(IOMod, T ++ S);
_ ->
- format(T ++ "ERROR: ~p ~n", [Chars])
+ format(IOMod, T ++ "ERROR: ~p ~n", [Chars])
end;
-write_event({Time, {info, _GL, {Pid, Info, _}}}) ->
+write_event({Time, {info, _GL, {Pid, Info, _}}},IOMod) ->
T = write_time(maybe_utc(Time)),
- format(T ++ add_node("~p~n",Pid),[Info]);
-write_event({Time, {error_report, _GL, {Pid, std_error, Rep}}}) ->
+ format(IOMod, T ++ add_node("~p~n",Pid),[Info]);
+write_event({Time, {error_report, _GL, {Pid, std_error, Rep}}},IOMod) ->
T = write_time(maybe_utc(Time)),
S = format_report(Rep),
- format(T ++ S ++ add_node("", Pid));
-write_event({Time, {info_report, _GL, {Pid, std_info, Rep}}}) ->
+ format(IOMod, T ++ S ++ add_node("", Pid));
+write_event({Time, {info_report, _GL, {Pid, std_info, Rep}}},IOMod) ->
T = write_time(maybe_utc(Time), "INFO REPORT"),
S = format_report(Rep),
- format(T ++ S ++ add_node("", Pid));
-write_event({Time, {info_msg, _GL, {Pid, Format, Args}}}) ->
+ format(IOMod, T ++ S ++ add_node("", Pid));
+write_event({Time, {info_msg, _GL, {Pid, Format, Args}}},IOMod) ->
T = write_time(maybe_utc(Time), "INFO REPORT"),
case catch io_lib:format(add_node(Format,Pid), Args) of
S when is_list(S) ->
- format(T ++ S);
+ format(IOMod, T ++ S);
_ ->
F = add_node("ERROR: ~p - ~p~n", Pid),
- format(T ++ F, [Format,Args])
+ format(IOMod, T ++ F, [Format,Args])
end;
-write_event({Time, {warning_report, _GL, {Pid, std_warning, Rep}}}) ->
+write_event({Time, {warning_report, _GL, {Pid, std_warning, Rep}}},IOMod) ->
T = write_time(maybe_utc(Time), "WARNING REPORT"),
S = format_report(Rep),
- format(T ++ S ++ add_node("", Pid));
-write_event({Time, {warning_msg, _GL, {Pid, Format, Args}}}) ->
+ format(IOMod, T ++ S ++ add_node("", Pid));
+write_event({Time, {warning_msg, _GL, {Pid, Format, Args}}},IOMod) ->
T = write_time(maybe_utc(Time), "WARNING REPORT"),
case catch io_lib:format(add_node(Format,Pid), Args) of
S when is_list(S) ->
- format(T ++ S);
+ format(IOMod, T ++ S);
_ ->
F = add_node("ERROR: ~p - ~p~n", Pid),
- format(T ++ F, [Format,Args])
+ format(IOMod, T ++ F, [Format,Args])
end;
-write_event({_Time, _Error}) ->
+write_event({_Time, _Error},_IOMod) ->
ok.
maybe_utc(Time) ->
@@ -178,8 +180,9 @@ maybe_utc(Time) ->
Time
end.
-format(String) -> io:format(user, String, []).
-format(String, Args) -> io:format(user, String, Args).
+format(IOMod, String) -> format(IOMod, String, []).
+format(io_lib, String, Args) -> io_lib:format(String, Args);
+format(io, String, Args) -> io:format(user, String, Args).
format_report(Rep) when is_list(Rep) ->
case string_p(Rep) of
diff --git a/lib/stdlib/src/escript.erl b/lib/stdlib/src/escript.erl
index cd1bacd2f5..ad49d89908 100644
--- a/lib/stdlib/src/escript.erl
+++ b/lib/stdlib/src/escript.erl
@@ -866,7 +866,7 @@ hidden_apply(App, M, F, Args) ->
catch
error:undef ->
case erlang:get_stacktrace() of
- [{M,F,Args} | _] ->
+ [{M,F,Args,_} | _] ->
Arity = length(Args),
Text = io_lib:format("Call to ~w:~w/~w in application ~w failed.\n",
[M, F, Arity, App]),
diff --git a/lib/stdlib/src/eval_bits.erl b/lib/stdlib/src/eval_bits.erl
index 2c7192a7e7..796c5b934d 100644
--- a/lib/stdlib/src/eval_bits.erl
+++ b/lib/stdlib/src/eval_bits.erl
@@ -31,8 +31,9 @@
%% @type evalfun(). A closure which evaluates an expression given an
%% environment
%%
-%% @type matchfun(). A closure which performs a match given a value, a
-%% pattern and an environment
+%% @type matchfun(). A closure which depending on its first argument
+%% can perform a match (given a value, a pattern and an environment),
+%% lookup a variable in the bindings, or add a new binding
%%
%% @type field(). Represents a field in a "bin".
@@ -144,7 +145,8 @@ eval_exp_field(Val, Size, Unit, binary, _, _) ->
bin_gen({bin,_,Fs}, Bin, Bs0, BBs0, Mfun, Efun) ->
bin_gen(Fs, Bin, Bs0, BBs0, Mfun, Efun, true).
-bin_gen([F|Fs], Bin, Bs0, BBs0, Mfun, Efun, Flag) ->
+bin_gen([F|Fs], Bin, Bs0, BBs0, Mfun, Efun, Flag)
+ when is_function(Mfun, 2), is_function(Efun, 2) ->
case bin_gen_field(F, Bin, Bs0, BBs0, Mfun, Efun) of
{match,Bs,BBs,Rest} ->
bin_gen(Fs, Rest, Bs, BBs, Mfun, Efun, Flag);
@@ -175,14 +177,14 @@ bin_gen_field({bin_element,Line,VE,Size0,Options0},
{Size1, [Type,{unit,Unit},Sign,Endian]} =
make_bit_type(Line, Size0, Options0),
V = erl_eval:partial_eval(VE),
- match_check_size(Size1, BBs0),
+ match_check_size(Mfun, Size1, BBs0),
{value, Size, _BBs} = Efun(Size1, BBs0),
case catch get_value(Bin, Type, Size, Unit, Sign, Endian) of
{Val,<<_/bitstring>>=Rest} ->
NewV = coerce_to_float(V, Type),
- case catch Mfun(NewV, Val, Bs0) of
+ case catch Mfun(match, {NewV,Val,Bs0}) of
{match,Bs} ->
- BBs = add_bin_binding(NewV, Bs, BBs0),
+ BBs = add_bin_binding(Mfun, NewV, Bs, BBs0),
{match,Bs,BBs,Rest};
_ ->
{nomatch,Rest}
@@ -205,7 +207,8 @@ bin_gen_field({bin_element,Line,VE,Size0,Options0},
match_bits(Fs, Bin, Bs0, BBs, Mfun, Efun, _) ->
match_bits(Fs, Bin, Bs0, BBs, Mfun, Efun).
-match_bits(Fs, Bin, Bs0, BBs, Mfun, Efun) ->
+match_bits(Fs, Bin, Bs0, BBs, Mfun, Efun)
+ when is_function(Mfun, 2), is_function(Efun, 2) ->
case catch match_bits_1(Fs, Bin, Bs0, BBs, Mfun, Efun) of
{match,Bs} -> {match,Bs};
invalid -> throw(invalid);
@@ -230,12 +233,12 @@ match_field_1({bin_element,Line,VE,Size0,Options0},
make_bit_type(Line, Size0, Options0),
V = erl_eval:partial_eval(VE),
Size2 = erl_eval:partial_eval(Size1),
- match_check_size(Size2, BBs0),
+ match_check_size(Mfun, Size2, BBs0),
{value, Size, _BBs} = Efun(Size2, BBs0),
{Val,Rest} = get_value(Bin, Type, Size, Unit, Sign, Endian),
NewV = coerce_to_float(V, Type),
- {match,Bs} = Mfun(NewV, Val, Bs0),
- BBs = add_bin_binding(NewV, Bs, BBs0),
+ {match,Bs} = Mfun(match, {NewV,Val,Bs0}),
+ BBs = add_bin_binding(Mfun, NewV, Bs, BBs0),
{Bs,BBs,Rest}.
%% Almost identical to the one in sys_pre_expand.
@@ -249,12 +252,12 @@ coerce_to_float({integer,L,I}=E, float) ->
coerce_to_float(E, _Type) ->
E.
-add_bin_binding({var,_,'_'}, _Bs, BBs) ->
+add_bin_binding(_, {var,_,'_'}, _Bs, BBs) ->
BBs;
-add_bin_binding({var,_,Name}, Bs, BBs) ->
- {value,Value} = erl_eval:binding(Name, Bs),
- erl_eval:add_binding(Name, Value, BBs);
-add_bin_binding(_, _Bs, BBs) ->
+add_bin_binding(Mfun, {var,_,Name}, Bs, BBs) ->
+ {value,Value} = Mfun(binding, {Name,Bs}),
+ Mfun(add_binding, {Name,Value,BBs});
+add_bin_binding(_, _, _Bs, BBs) ->
BBs.
get_value(Bin, integer, Size, Unit, Sign, Endian) ->
@@ -327,20 +330,20 @@ make_bit_type(_Line, Size, Type0) -> %Size evaluates to an integer or 'all'
{error,Reason} -> error(Reason)
end.
-match_check_size({var,_,V}, Bs) ->
- case erl_eval:binding(V, Bs) of
+match_check_size(Mfun, {var,_,V}, Bs) ->
+ case Mfun(binding, {V,Bs}) of
{value,_} -> ok;
unbound -> throw(invalid) % or, rather, error({unbound,V})
end;
-match_check_size({atom,_,all}, _Bs) ->
+match_check_size(_, {atom,_,all}, _Bs) ->
ok;
-match_check_size({atom,_,undefined}, _Bs) ->
+match_check_size(_, {atom,_,undefined}, _Bs) ->
ok;
-match_check_size({integer,_,_}, _Bs) ->
+match_check_size(_, {integer,_,_}, _Bs) ->
ok;
-match_check_size({value,_,_}, _Bs) ->
+match_check_size(_, {value,_,_}, _Bs) ->
ok; %From the debugger.
-match_check_size(_, _Bs) ->
+match_check_size(_, _, _Bs) ->
throw(invalid).
%% error(Reason) -> exception thrown
diff --git a/lib/stdlib/src/gen_event.erl b/lib/stdlib/src/gen_event.erl
index 1c4a73680b..d1dd074fba 100644
--- a/lib/stdlib/src/gen_event.erl
+++ b/lib/stdlib/src/gen_event.erl
@@ -667,16 +667,16 @@ report_error(_Handler, {swapped,_,_}, _, _, _) -> ok;
report_error(Handler, Reason, State, LastIn, SName) ->
Reason1 =
case Reason of
- {'EXIT',{undef,[{M,F,A}|MFAs]}} ->
+ {'EXIT',{undef,[{M,F,A,L}|MFAs]}} ->
case code:is_loaded(M) of
false ->
- {'module could not be loaded',[{M,F,A}|MFAs]};
+ {'module could not be loaded',[{M,F,A,L}|MFAs]};
_ ->
case erlang:function_exported(M, F, length(A)) of
true ->
- {undef,[{M,F,A}|MFAs]};
+ {undef,[{M,F,A,L}|MFAs]};
false ->
- {'function not exported',[{M,F,A}|MFAs]}
+ {'function not exported',[{M,F,A,L}|MFAs]}
end
end;
{'EXIT',Why} ->
diff --git a/lib/stdlib/src/gen_fsm.erl b/lib/stdlib/src/gen_fsm.erl
index f2f1365d3d..ea21136bdb 100644
--- a/lib/stdlib/src/gen_fsm.erl
+++ b/lib/stdlib/src/gen_fsm.erl
@@ -561,16 +561,16 @@ terminate(Reason, Name, Msg, Mod, StateName, StateData, Debug) ->
error_info(Reason, Name, Msg, StateName, StateData, Debug) ->
Reason1 =
case Reason of
- {undef,[{M,F,A}|MFAs]} ->
+ {undef,[{M,F,A,L}|MFAs]} ->
case code:is_loaded(M) of
false ->
- {'module could not be loaded',[{M,F,A}|MFAs]};
+ {'module could not be loaded',[{M,F,A,L}|MFAs]};
_ ->
case erlang:function_exported(M, F, length(A)) of
true ->
Reason;
false ->
- {'function not exported',[{M,F,A}|MFAs]}
+ {'function not exported',[{M,F,A,L}|MFAs]}
end
end;
_ ->
diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl
index 09d94a9c40..b8ea3a4de2 100644
--- a/lib/stdlib/src/gen_server.erl
+++ b/lib/stdlib/src/gen_server.erl
@@ -729,16 +729,16 @@ error_info(_Reason, application_controller, _Msg, _State, _Debug) ->
error_info(Reason, Name, Msg, State, Debug) ->
Reason1 =
case Reason of
- {undef,[{M,F,A}|MFAs]} ->
+ {undef,[{M,F,A,L}|MFAs]} ->
case code:is_loaded(M) of
false ->
- {'module could not be loaded',[{M,F,A}|MFAs]};
+ {'module could not be loaded',[{M,F,A,L}|MFAs]};
_ ->
case erlang:function_exported(M, F, length(A)) of
true ->
Reason;
false ->
- {'function not exported',[{M,F,A}|MFAs]}
+ {'function not exported',[{M,F,A,L}|MFAs]}
end
end;
_ ->
diff --git a/lib/stdlib/src/lib.erl b/lib/stdlib/src/lib.erl
index c303ae60b5..314fd60903 100644
--- a/lib/stdlib/src/lib.erl
+++ b/lib/stdlib/src/lib.erl
@@ -173,12 +173,12 @@ format_fun(Fun) when is_function(Fun) ->
analyze_exception(error, Term, Stack) ->
case {is_stacktrace(Stack), Stack, Term} of
- {true, [{_M,_F,As}=MFA|MFAs], function_clause} when is_list(As) ->
- {Term,[MFA],MFAs};
- {true, [{shell,F,A}], function_clause} when is_integer(A) ->
+ {true, [{_,_,As,_}=MFAL|MFAs], function_clause} when is_list(As) ->
+ {Term,[MFAL],MFAs};
+ {true, [{shell,F,A,_}], function_clause} when is_integer(A) ->
{Term, [{F,A}], []};
- {true, [{_M,_F,_AorAs}=MFA|MFAs], undef} ->
- {Term,[MFA],MFAs};
+ {true, [{_,_,_,_}=MFAL|MFAs], undef} ->
+ {Term,[MFAL],MFAs};
{true, _, _} ->
{Term,[],Stack};
{false, _, _} ->
@@ -194,9 +194,11 @@ analyze_exception(_Class, Term, Stack) ->
is_stacktrace([]) ->
true;
-is_stacktrace([{M,F,A}|Fs]) when is_atom(M), is_atom(F), is_integer(A) ->
+is_stacktrace([{M,F,A,I}|Fs])
+ when is_atom(M), is_atom(F), is_integer(A), is_list(I) ->
is_stacktrace(Fs);
-is_stacktrace([{M,F,As}|Fs]) when is_atom(M), is_atom(F), length(As) >= 0 ->
+is_stacktrace([{M,F,As,I}|Fs])
+ when is_atom(M), is_atom(F), length(As) >= 0, is_list(I) ->
is_stacktrace(Fs);
is_stacktrace(_) ->
false.
@@ -225,9 +227,9 @@ explain_reason(function_clause, error, [{F,A}], _PF, _S) ->
%% Shell commands
FAs = io_lib:fwrite(<<"~w/~w">>, [F, A]),
[<<"no function clause matching call to ">> | FAs];
-explain_reason(function_clause, error=Cl, [{M,F,As}], PF, S) ->
+explain_reason(function_clause, error=Cl, [{M,F,As,Loc}], PF, S) ->
Str = <<"no function clause matching ">>,
- format_errstr_call(Str, Cl, {M,F}, As, PF, S);
+ [format_errstr_call(Str, Cl, {M,F}, As, PF, S),$\s|location(Loc)];
explain_reason(if_clause, error, [], _PF, _S) ->
<<"no true branch found when evaluating an if expression">>;
explain_reason(noproc, error, [], _PF, _S) ->
@@ -242,11 +244,11 @@ explain_reason({try_clause,V}, error=Cl, [], PF, S) ->
%% "there is no try clause with a true guard sequence and a
%% pattern matching..."
format_value(V, <<"no try clause matching ">>, Cl, PF, S);
-explain_reason(undef, error, [{M,F,A}], _PF, _S) ->
+explain_reason(undef, error, [{M,F,A,_}], _PF, _S) ->
%% Only the arity is displayed, not the arguments, if there are any.
io_lib:fwrite(<<"undefined function ~s">>,
[mfa_to_string(M, F, n_args(A))]);
-explain_reason({shell_undef,F,A}, error, [], _PF, _S) ->
+explain_reason({shell_undef,F,A,_}, error, [], _PF, _S) ->
%% Give nicer reports for undefined shell functions
%% (but not when the user actively calls shell_default:F(...)).
io_lib:fwrite(<<"undefined shell command ~s/~w">>, [F, n_args(A)]);
@@ -292,17 +294,19 @@ argss(I) ->
io_lib:fwrite(<<"~w arguments">>, [I]).
format_stacktrace1(S0, Stack0, PF, SF) ->
- Stack1 = lists:dropwhile(fun({M,F,A}) -> SF(M, F, A)
+ Stack1 = lists:dropwhile(fun({M,F,A,_}) -> SF(M, F, A)
end, lists:reverse(Stack0)),
S = [" " | S0],
Stack = lists:reverse(Stack1),
format_stacktrace2(S, Stack, 1, PF).
-format_stacktrace2(S, [{M,F,A}|Fs], N, PF) when is_integer(A) ->
- [io_lib:fwrite(<<"~s~s ~s">>,
- [sep(N, S), origin(N, M, F, A), mfa_to_string(M, F, A)])
+format_stacktrace2(S, [{M,F,A,L}|Fs], N, PF) when is_integer(A) ->
+ [io_lib:fwrite(<<"~s~s ~s ~s">>,
+ [sep(N, S), origin(N, M, F, A),
+ mfa_to_string(M, F, A),
+ location(L)])
| format_stacktrace2(S, Fs, N + 1, PF)];
-format_stacktrace2(S, [{M,F,As}|Fs], N, PF) when is_list(As) ->
+format_stacktrace2(S, [{M,F,As,_}|Fs], N, PF) when is_list(As) ->
A = length(As),
CalledAs = [S,<<" called as ">>],
C = format_call("", CalledAs, {M,F}, As, PF),
@@ -313,6 +317,16 @@ format_stacktrace2(S, [{M,F,As}|Fs], N, PF) when is_list(As) ->
format_stacktrace2(_S, [], _N, _PF) ->
"".
+location(L) ->
+ File = proplists:get_value(file, L),
+ Line = proplists:get_value(line, L),
+ if
+ File =/= undefined, Line =/= undefined ->
+ io_lib:format("(~s, line ~w)", [File, Line]);
+ true ->
+ ""
+ end.
+
sep(1, S) -> S;
sep(_, S) -> [$\n | S].
diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl
index 5129ba5074..c1285dab60 100644
--- a/lib/stdlib/src/otp_internal.erl
+++ b/lib/stdlib/src/otp_internal.erl
@@ -330,22 +330,22 @@ obsolete_1(erlang, fault, 2) ->
obsolete_1(file, rawopen, 2) ->
{removed, "deprecated (will be removed in R13B); use file:open/2 with the raw option"};
-obsolete_1(http, request, 1) -> {deprecated,{httpc,request,1},"R15B"};
-obsolete_1(http, request, 2) -> {deprecated,{httpc,request,2},"R15B"};
-obsolete_1(http, request, 4) -> {deprecated,{httpc,request,4},"R15B"};
-obsolete_1(http, request, 5) -> {deprecated,{httpc,request,5},"R15B"};
-obsolete_1(http, cancel_request, 1) -> {deprecated,{httpc,cancel_request,1},"R15B"};
-obsolete_1(http, cancel_request, 2) -> {deprecated,{httpc,cancel_request,2},"R15B"};
-obsolete_1(http, set_option, 2) -> {deprecated,{httpc,set_option,2},"R15B"};
-obsolete_1(http, set_option, 3) -> {deprecated,{httpc,set_option,3},"R15B"};
-obsolete_1(http, set_options, 1) -> {deprecated,{httpc,set_options,1},"R15B"};
-obsolete_1(http, set_options, 2) -> {deprecated,{httpc,set_options,2},"R15B"};
-obsolete_1(http, verify_cookies, 2) -> {deprecated,{httpc,verify_cookies,2},"R15B"};
-obsolete_1(http, verify_cookies, 3) -> {deprecated,{httpc,verify_cookies,3},"R15B"};
-obsolete_1(http, cookie_header, 1) -> {deprecated,{httpc,cookie_header,1},"R15B"};
-obsolete_1(http, cookie_header, 2) -> {deprecated,{httpc,cookie_header,2},"R15B"};
-obsolete_1(http, stream_next, 1) -> {deprecated,{httpc,stream_next,1},"R15B"};
-obsolete_1(http, default_profile, 0) -> {deprecated,{httpc,default_profile,0},"R15B"};
+obsolete_1(http, request, 1) -> {removed,{httpc,request,1},"R15B"};
+obsolete_1(http, request, 2) -> {removed,{httpc,request,2},"R15B"};
+obsolete_1(http, request, 4) -> {removed,{httpc,request,4},"R15B"};
+obsolete_1(http, request, 5) -> {removed,{httpc,request,5},"R15B"};
+obsolete_1(http, cancel_request, 1) -> {removed,{httpc,cancel_request,1},"R15B"};
+obsolete_1(http, cancel_request, 2) -> {removed,{httpc,cancel_request,2},"R15B"};
+obsolete_1(http, set_option, 2) -> {removed,{httpc,set_option,2},"R15B"};
+obsolete_1(http, set_option, 3) -> {removed,{httpc,set_option,3},"R15B"};
+obsolete_1(http, set_options, 1) -> {removed,{httpc,set_options,1},"R15B"};
+obsolete_1(http, set_options, 2) -> {removed,{httpc,set_options,2},"R15B"};
+obsolete_1(http, verify_cookies, 2) -> {removed,{httpc,store_cookies,2},"R15B"};
+obsolete_1(http, verify_cookies, 3) -> {removed,{httpc,store_cookies,3},"R15B"};
+obsolete_1(http, cookie_header, 1) -> {removed,{httpc,cookie_header,1},"R15B"};
+obsolete_1(http, cookie_header, 2) -> {removed,{httpc,cookie_header,2},"R15B"};
+obsolete_1(http, stream_next, 1) -> {removed,{httpc,stream_next,1},"R15B"};
+obsolete_1(http, default_profile, 0) -> {removed,{httpc,default_profile,0},"R15B"};
obsolete_1(httpd, start, 0) -> {removed,{inets,start,[2,3]},"R14B"};
obsolete_1(httpd, start, 1) -> {removed,{inets,start,[2,3]},"R14B"};
@@ -449,7 +449,7 @@ obsolete_1(ssl_pkix, decode_cert, A) when A =:= 1; A =:= 2 ->
%% Added in R13B04.
obsolete_1(erlang, concat_binary, 1) ->
- {deprecated,{erlang,list_to_binary,1},"R15B"};
+ {removed,{erlang,list_to_binary,1},"R15B"};
%% Added in R14A.
obsolete_1(ssl, peercert, 2) ->
@@ -469,6 +469,10 @@ obsolete_1(docb_transform, _, _) ->
obsolete_1(docb_xml_check, _, _) ->
{deprecated,"the DocBuilder application is deprecated (will be removed in R15B)"};
+%% Added in R15B
+obsolete_1(asn1rt, F, _) when F == load_driver; F == unload_driver ->
+ {deprecated,"deprecated (will be removed in R16A); has no effect as drivers are no longer used."};
+
obsolete_1(_, _, _) ->
no.
diff --git a/lib/stdlib/src/qlc.erl b/lib/stdlib/src/qlc.erl
index 5ca04ff023..f5e180b4bd 100644
--- a/lib/stdlib/src/qlc.erl
+++ b/lib/stdlib/src/qlc.erl
@@ -123,7 +123,7 @@
-record(setup, {parent}).
--define(THROWN_ERROR, {?MODULE, throw_error, _}).
+-define(THROWN_ERROR, {?MODULE, throw_error, _, _}).
-export_type([query_handle/0]).
@@ -3701,7 +3701,8 @@ lookup_join(F1, C1, LuF, C2, Rev) ->
maybe_error_logger(allowed, _) ->
ok;
maybe_error_logger(Name, Why) ->
- [_, _, {?MODULE,maybe_error_logger,_} | Stacktrace] = expand_stacktrace(),
+ [_, _, {?MODULE,maybe_error_logger,_,_} | Stacktrace] =
+ expand_stacktrace(),
Trimmer = fun(M, _F, _A) -> M =:= erl_eval end,
Formater = fun(Term, I) -> io_lib:print(Term, I, 80, -1) end,
X = lib:format_stacktrace(1, Stacktrace, Trimmer, Formater),
@@ -3720,7 +3721,7 @@ expand_stacktrace() ->
expand_stacktrace(D) ->
_ = erlang:system_flag(backtrace_depth, D),
{'EXIT', {foo, Stacktrace}} = (catch erlang:error(foo)),
- L = lists:takewhile(fun({M,_,_}) -> M =/= ?MODULE
+ L = lists:takewhile(fun({M,_,_,_}) -> M =/= ?MODULE
end, lists:reverse(Stacktrace)),
if
length(L) < 3 andalso length(Stacktrace) =:= D ->
diff --git a/lib/stdlib/src/re.erl b/lib/stdlib/src/re.erl
index e08258a535..99bcbd722e 100644
--- a/lib/stdlib/src/re.erl
+++ b/lib/stdlib/src/re.erl
@@ -573,10 +573,10 @@ ucompile(RE,Options) ->
re:compile(unicode:characters_to_binary(RE,unicode),Options)
catch
error:AnyError ->
- {'EXIT',{new_stacktrace,[{Mod,_,L}|Rest]}} =
+ {'EXIT',{new_stacktrace,[{Mod,_,L,Loc}|Rest]}} =
(catch erlang:error(new_stacktrace,
[RE,Options])),
- erlang:raise(error,AnyError,[{Mod,compile,L}|Rest])
+ erlang:raise(error,AnyError,[{Mod,compile,L,Loc}|Rest])
end.
@@ -585,10 +585,10 @@ urun(Subject,RE,Options) ->
urun2(Subject,RE,Options)
catch
error:AnyError ->
- {'EXIT',{new_stacktrace,[{Mod,_,L}|Rest]}} =
+ {'EXIT',{new_stacktrace,[{Mod,_,L,Loc}|Rest]}} =
(catch erlang:error(new_stacktrace,
[Subject,RE,Options])),
- erlang:raise(error,AnyError,[{Mod,run,L}|Rest])
+ erlang:raise(error,AnyError,[{Mod,run,L,Loc}|Rest])
end.
urun2(Subject0,RE0,Options0) ->
@@ -625,20 +625,20 @@ grun(Subject,RE,{Options,NeedClean}) ->
grun2(Subject,RE,{Options,NeedClean})
catch
error:AnyError ->
- {'EXIT',{new_stacktrace,[{Mod,_,L}|Rest]}} =
+ {'EXIT',{new_stacktrace,[{Mod,_,L,Loc}|Rest]}} =
(catch erlang:error(new_stacktrace,
[Subject,RE,Options])),
- erlang:raise(error,AnyError,[{Mod,run,L}|Rest])
+ erlang:raise(error,AnyError,[{Mod,run,L,Loc}|Rest])
end;
grun(Subject,RE,{Options,NeedClean,OrigRE}) ->
try
grun2(Subject,RE,{Options,NeedClean})
catch
error:AnyError ->
- {'EXIT',{new_stacktrace,[{Mod,_,L}|Rest]}} =
+ {'EXIT',{new_stacktrace,[{Mod,_,L,Loc}|Rest]}} =
(catch erlang:error(new_stacktrace,
[Subject,OrigRE,Options])),
- erlang:raise(error,AnyError,[{Mod,run,L}|Rest])
+ erlang:raise(error,AnyError,[{Mod,run,L,Loc}|Rest])
end.
grun2(Subject,RE,{Options,NeedClean}) ->
diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl
index e3e23e09bc..964697cae6 100644
--- a/lib/stdlib/src/shell.erl
+++ b/lib/stdlib/src/shell.erl
@@ -1088,7 +1088,7 @@ shell_default(F,As,Bs) ->
end.
shell_undef(F,A) ->
- erlang:error({shell_undef,F,A}).
+ erlang:error({shell_undef,F,A,[]}).
local_func_handler(Shell, RT, Ef) ->
H = fun(Lf) ->
diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl
index dc31647eb5..36cc7f4f4b 100644
--- a/lib/stdlib/src/supervisor.erl
+++ b/lib/stdlib/src/supervisor.erl
@@ -661,6 +661,9 @@ do_restart(_, normal, Child, State) ->
do_restart(_, shutdown, Child, State) ->
NState = state_del_child(Child, State),
{ok, NState};
+do_restart(_, {shutdown, _Term}, Child, State) ->
+ NState = state_del_child(Child, State),
+ {ok, NState};
do_restart(transient, Reason, Child, State) ->
report_error(child_terminated, Reason, Child, State#state.name),
restart(Child, State);
diff --git a/lib/stdlib/src/unicode.erl b/lib/stdlib/src/unicode.erl
index a5d9965ca2..e9b90befe6 100644
--- a/lib/stdlib/src/unicode.erl
+++ b/lib/stdlib/src/unicode.erl
@@ -73,7 +73,7 @@ characters_to_list_int(ML, Encoding) ->
_ ->
badarg
end,
- {'EXIT',{new_stacktrace,[{Mod,_,L}|Rest]}} =
+ {'EXIT',{new_stacktrace,[{Mod,_,L,_}|Rest]}} =
(catch erlang:error(new_stacktrace,
[ML,Encoding])),
erlang:raise(error,TheError,[{Mod,characters_to_list,L}|Rest])
@@ -109,7 +109,7 @@ characters_to_binary(ML) ->
_ ->
badarg
end,
- {'EXIT',{new_stacktrace,[{Mod,_,L}|Rest]}} =
+ {'EXIT',{new_stacktrace,[{Mod,_,L,_}|Rest]}} =
(catch erlang:error(new_stacktrace,
[ML])),
erlang:raise(error,TheError,[{Mod,characters_to_binary,L}|Rest])
@@ -127,7 +127,7 @@ characters_to_binary_int(ML,InEncoding) ->
_ ->
badarg
end,
- {'EXIT',{new_stacktrace,[{Mod,_,L}|Rest]}} =
+ {'EXIT',{new_stacktrace,[{Mod,_,L,_}|Rest]}} =
(catch erlang:error(new_stacktrace,
[ML,InEncoding])),
erlang:raise(error,TheError,[{Mod,characters_to_binary,L}|Rest])
@@ -159,7 +159,7 @@ characters_to_binary(ML, latin1, Uni) when is_binary(ML) and ((Uni =:= utf8) or
_ ->
badarg
end,
- {'EXIT',{new_stacktrace,[{Mod,_,L}|Rest]}} =
+ {'EXIT',{new_stacktrace,[{Mod,_,L,_}|Rest]}} =
(catch erlang:error(new_stacktrace,
[ML,latin1,Uni])),
erlang:raise(error,TheError,
@@ -181,7 +181,7 @@ characters_to_binary(ML,Uni,latin1) when is_binary(ML) and ((Uni =:= utf8) or
_ ->
badarg
end,
- {'EXIT',{new_stacktrace,[{Mod,_,L}|Rest]}} =
+ {'EXIT',{new_stacktrace,[{Mod,_,L,_}|Rest]}} =
(catch erlang:error(new_stacktrace,
[ML,Uni,latin1])),
erlang:raise(error,TheError,
@@ -200,7 +200,7 @@ characters_to_binary(ML, InEncoding, OutEncoding) ->
_ ->
badarg
end,
- {'EXIT',{new_stacktrace,[{Mod,_,L}|Rest]}} =
+ {'EXIT',{new_stacktrace,[{Mod,_,L,_}|Rest]}} =
(catch erlang:error(new_stacktrace,
[ML,InEncoding,OutEncoding])),
erlang:raise(error,TheError,[{Mod,characters_to_binary,L}|Rest])