summaryrefslogtreecommitdiff
path: root/lib/stdlib/src
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r--lib/stdlib/src/Makefile11
-rw-r--r--lib/stdlib/src/beam_lib.erl1
-rw-r--r--lib/stdlib/src/c.erl82
-rw-r--r--lib/stdlib/src/calendar.erl3
-rw-r--r--lib/stdlib/src/edlin.erl5
-rw-r--r--lib/stdlib/src/edlin_expand.erl78
-rw-r--r--lib/stdlib/src/erl_error.erl219
-rw-r--r--lib/stdlib/src/erl_eval.erl26
-rw-r--r--lib/stdlib/src/erl_expand_records.erl8
-rw-r--r--lib/stdlib/src/erl_internal.erl13
-rw-r--r--lib/stdlib/src/erl_lint.erl412
-rw-r--r--lib/stdlib/src/erl_parse.yrl23
-rw-r--r--lib/stdlib/src/erl_pp.erl78
-rw-r--r--lib/stdlib/src/erl_scan.erl160
-rw-r--r--lib/stdlib/src/erl_tar.erl85
-rw-r--r--lib/stdlib/src/escript.erl38
-rw-r--r--lib/stdlib/src/ets.erl4
-rw-r--r--lib/stdlib/src/eval_bits.erl25
-rw-r--r--lib/stdlib/src/filelib.erl109
-rw-r--r--lib/stdlib/src/filename.erl4
-rw-r--r--lib/stdlib/src/gen.erl97
-rw-r--r--lib/stdlib/src/gen_event.erl256
-rw-r--r--lib/stdlib/src/gen_fsm.erl343
-rw-r--r--lib/stdlib/src/gen_server.erl339
-rw-r--r--lib/stdlib/src/gen_statem.erl441
-rw-r--r--lib/stdlib/src/io.erl12
-rw-r--r--lib/stdlib/src/io_lib.erl29
-rw-r--r--lib/stdlib/src/io_lib_pretty.erl3
-rw-r--r--lib/stdlib/src/maps.erl3
-rw-r--r--lib/stdlib/src/otp_internal.erl988
-rw-r--r--lib/stdlib/src/otp_internal.hrl36
-rw-r--r--lib/stdlib/src/proc_lib.erl411
-rw-r--r--lib/stdlib/src/proplists.erl20
-rw-r--r--lib/stdlib/src/qlc.erl4
-rw-r--r--lib/stdlib/src/qlc_pt.erl28
-rw-r--r--lib/stdlib/src/queue.erl2
-rw-r--r--lib/stdlib/src/random.erl2
-rw-r--r--lib/stdlib/src/shell_default.erl15
-rw-r--r--lib/stdlib/src/shell_docs.erl684
-rw-r--r--lib/stdlib/src/stdlib.app.src3
-rw-r--r--lib/stdlib/src/supervisor.erl261
-rw-r--r--lib/stdlib/src/supervisor_bridge.erl176
-rw-r--r--lib/stdlib/src/sys.erl5
-rw-r--r--lib/stdlib/src/zip.erl148
44 files changed, 4012 insertions, 1678 deletions
diff --git a/lib/stdlib/src/Makefile b/lib/stdlib/src/Makefile
index 86003c953d..c410b36964 100644
--- a/lib/stdlib/src/Makefile
+++ b/lib/stdlib/src/Makefile
@@ -112,6 +112,7 @@ MODULES= \
sets \
shell \
shell_default \
+ shell_docs \
slave \
sofs \
string \
@@ -133,7 +134,7 @@ HRL_FILES= \
../include/qlc.hrl \
../include/zip.hrl
-INTERNAL_HRL_FILES= dets.hrl erl_tar.hrl
+INTERNAL_HRL_FILES= dets.hrl erl_tar.hrl otp_internal.hrl
ERL_FILES= $(MODULES:%=%.erl)
@@ -149,6 +150,12 @@ APPUP_FILE= stdlib.appup
APPUP_SRC= $(APPUP_FILE).src
APPUP_TARGET= $(EBIN)/$(APPUP_FILE)
+ifeq ($(TARGET),win32)
+ EXE_SUFFIX=.exe
+else
+ EXE_SUFFIX=
+endif
+
# ----------------------------------------------------
# FLAGS
# ----------------------------------------------------
@@ -207,7 +214,7 @@ $(APPUP_TARGET): $(APPUP_SRC) ../vsn.mk
$(vsn_verbose)sed -e 's;%VSN%;$(VSN);' $< > $@
unicode_util.erl: ../uc_spec/*
- escript ../uc_spec/gen_unicode_mod.escript
+ escript$(EXE_SUFFIX) ../uc_spec/gen_unicode_mod.escript
# ----------------------------------------------------
# Release Target
diff --git a/lib/stdlib/src/beam_lib.erl b/lib/stdlib/src/beam_lib.erl
index aa992f17ab..967ed33c61 100644
--- a/lib/stdlib/src/beam_lib.erl
+++ b/lib/stdlib/src/beam_lib.erl
@@ -19,6 +19,7 @@
%%
-module(beam_lib).
-behaviour(gen_server).
+-compile({nowarn_deprecated_function,{crypto,block_decrypt,4}}).
%% Avoid warning for local function error/1 clashing with autoimported BIF.
-compile({no_auto_import,[error/1]}).
diff --git a/lib/stdlib/src/c.erl b/lib/stdlib/src/c.erl
index 0362b72536..6af3951604 100644
--- a/lib/stdlib/src/c.erl
+++ b/lib/stdlib/src/c.erl
@@ -19,6 +19,8 @@
%%
-module(c).
+-include_lib("kernel/include/eep48.hrl").
+
%% Utilities to use from shell.
%% Avoid warning for local function error/2 clashing with autoimported BIF.
@@ -28,6 +30,7 @@
lc_batch/0, lc_batch/1,
i/3,pid/3,m/0,m/1,mm/0,lm/0,
bt/1, q/0,
+ h/1,h/2,h/3,ht/1,ht/2,ht/3,
erlangrc/0,erlangrc/1,bi/1, flush/0, regs/0, uptime/0,
nregs/0,pwd/0,ls/0,ls/1,cd/1,memory/1,memory/0, xm/1]).
@@ -48,6 +51,9 @@ help() ->
"cd(Dir) -- change working directory\n"
"flush() -- flush any messages sent to the shell\n"
"help() -- help info\n"
+ "h(M) -- module documentation\n"
+ "h(M,F) -- module function documentation\n"
+ "h(M,F,A) -- module function arity documentation\n"
"i() -- information about the system\n"
"ni() -- information about the networked system\n"
"i(X,Y,Z) -- information about pid <X,Y,Z>\n"
@@ -147,6 +153,82 @@ c(SrcFile, NewOpts, Filter, BeamFile, Info) ->
format("Recompiling ~ts\n", [SrcFile]),
safe_recompile(SrcFile, Options, BeamFile).
+-type h_return() :: ok | {error, missing | {unknown_format, unicode:chardata()}}.
+-type ht_return() :: h_return() | {error, type_missing}.
+-type hf_return() :: h_return() | {error, function_missing}.
+
+-spec h(module()) -> h_return().
+h(Module) ->
+ case code:get_doc(Module) of
+ {ok, #docs_v1{ format = ?NATIVE_FORMAT } = Docs} ->
+ format_docs(shell_docs:render(Module, Docs));
+ {ok, #docs_v1{ format = Enc }} ->
+ {error, {unknown_format, Enc}};
+ Error ->
+ Error
+ end.
+
+-spec h(module(),function()) -> hf_return().
+h(Module,Function) ->
+ case code:get_doc(Module) of
+ {ok, #docs_v1{ format = ?NATIVE_FORMAT } = Docs} ->
+ format_docs(shell_docs:render(Module, Function, Docs));
+ {ok, #docs_v1{ format = Enc }} ->
+ {error, {unknown_format, Enc}};
+ Error ->
+ Error
+ end.
+
+-spec h(module(),function(),arity()) -> hf_return().
+h(Module,Function,Arity) ->
+ case code:get_doc(Module) of
+ {ok, #docs_v1{ format = ?NATIVE_FORMAT } = Docs} ->
+ format_docs(shell_docs:render(Module, Function, Arity, Docs));
+ {ok, #docs_v1{ format = Enc }} ->
+ {error, {unknown_format, Enc}};
+ Error ->
+ Error
+ end.
+
+-spec ht(module()) -> h_return().
+ht(Module) ->
+ case code:get_doc(Module) of
+ {ok, #docs_v1{ format = ?NATIVE_FORMAT } = Docs} ->
+ format_docs(shell_docs:render_type(Module, Docs));
+ {ok, #docs_v1{ format = Enc }} ->
+ {error, {unknown_format, Enc}};
+ Error ->
+ Error
+ end.
+
+-spec ht(module(),Type :: atom()) -> ht_return().
+ht(Module,Type) ->
+ case code:get_doc(Module) of
+ {ok, #docs_v1{ format = ?NATIVE_FORMAT } = Docs} ->
+ format_docs(shell_docs:render_type(Module, Type, Docs));
+ {ok, #docs_v1{ format = Enc }} ->
+ {error, {unknown_format, Enc}};
+ Error ->
+ Error
+ end.
+
+-spec ht(module(),Type :: atom(),arity()) ->
+ ht_return().
+ht(Module,Type,Arity) ->
+ case code:get_doc(Module) of
+ {ok, #docs_v1{ format = ?NATIVE_FORMAT } = Docs} ->
+ format_docs(shell_docs:render_type(Module, Type, Arity, Docs));
+ {ok, #docs_v1{ format = Enc }} ->
+ {error, {unknown_format, Enc}};
+ Error ->
+ Error
+ end.
+
+format_docs({error,_} = E) ->
+ E;
+format_docs(Docs) ->
+ format("~ts",[Docs]).
+
old_options(Info) ->
case lists:keyfind(options, 1, Info) of
{options, Opts} -> Opts;
diff --git a/lib/stdlib/src/calendar.erl b/lib/stdlib/src/calendar.erl
index ef6d1882e6..2f95f54312 100644
--- a/lib/stdlib/src/calendar.erl
+++ b/lib/stdlib/src/calendar.erl
@@ -54,7 +54,8 @@
valid_date/1,
valid_date/3]).
--deprecated([{local_time_to_universal_time,1}]).
+-deprecated([{local_time_to_universal_time,1,
+ "use calendar:local_time_to_universal_time_dst/1 instead"}]).
-define(SECONDS_PER_MINUTE, 60).
-define(SECONDS_PER_HOUR, 3600).
diff --git a/lib/stdlib/src/edlin.erl b/lib/stdlib/src/edlin.erl
index f027d05f55..6078c5e67b 100644
--- a/lib/stdlib/src/edlin.erl
+++ b/lib/stdlib/src/edlin.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2018. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2019. 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.
@@ -352,9 +352,6 @@ do_op({blink,C,M}, Bef=[$$,$$|_], Aft, Rs) ->
%% don't blink after a $
do_op({blink,C,_}, Bef=[$$|_], Aft, Rs) ->
do_op({insert,C}, Bef, Aft, Rs);
-%do_op({blink,C,M}, Bef, [], Rs) ->
-% N = over_paren(Bef, C, M),
-% {blink,N+1,{[C|Bef],[]},[{move_rel,-(N+1)},{put_chars,[C]}|Rs]};
do_op({blink,C,M}, Bef, Aft, Rs) ->
case over_paren(Bef, C, M) of
beep ->
diff --git a/lib/stdlib/src/edlin_expand.erl b/lib/stdlib/src/edlin_expand.erl
index bdcefda6e5..bb6ad26d8f 100644
--- a/lib/stdlib/src/edlin_expand.erl
+++ b/lib/stdlib/src/edlin_expand.erl
@@ -32,35 +32,71 @@
%% function name must be on the same line. CurrentBefore is reversed
%% and over_word/3 reverses the characters it finds. In certain cases
%% possible expansions are printed.
+%%
+%% The function also handles expansion with "h(" for module and functions.
expand(Bef0) ->
{Bef1,Word,_} = edlin:over_word(Bef0, [], 0),
case over_white(Bef1, [], 0) of
- {[$:|Bef2],_White,_Nwh} ->
+ {[$,|Bef2],_White,_Nwh} ->
+ {Bef3,_White1,_Nwh1} = over_white(Bef2, [], 0),
+ {Bef4,Mod,_Nm} = edlin:over_word(Bef3, [], 0),
+ case expand_function(Bef4) of
+ help ->
+ expand_function_name(Mod, Word, ",");
+ _ ->
+ expand_module_name(Word, ",")
+ end;
+ {[$:|Bef2],_White,_Nwh} ->
{Bef3,_White1,_Nwh1} = over_white(Bef2, [], 0),
{_,Mod,_Nm} = edlin:over_word(Bef3, [], 0),
- expand_function_name(Mod, Word);
+ expand_function_name(Mod, Word, "(");
{_,_,_} ->
- expand_module_name(Word)
+ CompleteChar
+ = case expand_function(Bef1) of
+ help -> ",";
+ _ -> ":"
+ end,
+ expand_module_name(Word, CompleteChar)
end.
-expand_module_name(Prefix) ->
- match(Prefix, code:all_loaded(), ":").
+expand_function("("++Str) ->
+ case edlin:over_word(Str, [], 0) of
+ {_,"h",_} ->
+ help;
+ {_,"ht",_} ->
+ help_type;
+ _ ->
+ module
+ end;
+expand_function(_) ->
+ module.
+
+expand_module_name("",_) ->
+ {no, [], []};
+expand_module_name(Prefix,CompleteChar) ->
+ match(Prefix, [{list_to_atom(M),P} || {M,P,_} <- code:all_available()], CompleteChar).
-expand_function_name(ModStr, FuncPrefix) ->
+expand_function_name(ModStr, FuncPrefix, CompleteChar) ->
case to_atom(ModStr) of
{ok, Mod} ->
- case erlang:module_loaded(Mod) of
- true ->
- L = Mod:module_info(),
- case lists:keyfind(exports, 1, L) of
- {_, Exports} ->
- match(FuncPrefix, Exports, "(");
- _ ->
- {no, [], []}
- end;
- false ->
- {no, [], []}
- end;
+ Exports =
+ case erlang:module_loaded(Mod) of
+ true ->
+ Mod:module_info(exports);
+ false ->
+ case beam_lib:chunks(code:which(Mod), [exports]) of
+ {ok, {Mod, [{exports,E}]}} ->
+ E;
+ _ ->
+ {no, [], []}
+ end
+ end,
+ case Exports of
+ {no, [], []} ->
+ {no, [], []};
+ Exports ->
+ match(FuncPrefix, Exports, CompleteChar)
+ end;
error ->
{no, [], []}
end.
@@ -99,8 +135,10 @@ match(Prefix, Alts, Extra0) ->
{no, [], []}
end.
-flat_write(T) ->
- lists:flatten(io_lib:fwrite("~tw",[T])).
+flat_write(T) when is_atom(T) ->
+ lists:flatten(io_lib:fwrite("~tw",[T]));
+flat_write(S) ->
+ S.
%% Return the list of names L in multiple columns.
format_matches(L) ->
diff --git a/lib/stdlib/src/erl_error.erl b/lib/stdlib/src/erl_error.erl
index fdcb9e824c..5fbf5a6282 100644
--- a/lib/stdlib/src/erl_error.erl
+++ b/lib/stdlib/src/erl_error.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2018. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2019. 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.
@@ -19,7 +19,7 @@
%%
-module(erl_error).
--export([format_exception/6, format_exception/7,
+-export([format_exception/6, format_exception/7, format_exception/8,
format_stacktrace/4, format_stacktrace/5,
format_call/4, format_call/5, format_fun/1, format_fun/2]).
@@ -38,20 +38,34 @@ format_exception(I, Class, Reason, StackTrace, StackFun, FormatFun) ->
%% -> iolist() | unicode:charlist() (no \n at end)
%% FormatFun = fun(Term, I) -> iolist() | unicode:charlist().
-format_exception(I, Class, Reason, StackTrace, StackFun, FormatFun, Encoding)
+format_exception(I, Class, Reason, StackTrace, StackFun, FormatFun, Encoding) ->
+ FF = wrap_format_fun_2(FormatFun),
+ format_exception(I, Class, Reason, StackTrace, StackFun, FF, Encoding, -1).
+
+format_exception(I, Class, Reason, StackTrace, StackFun, FormatFun, Encoding,
+ CharsLimit)
when is_integer(I), I >= 1, is_function(StackFun, 3),
- is_function(FormatFun, 2) ->
+ is_function(FormatFun, 3), is_integer(CharsLimit) ->
S = n_spaces(I-1),
{Term,Trace1,Trace} = analyze_exception(Class, Reason, StackTrace),
- Expl0 = explain_reason(Term, Class, Trace1, FormatFun, S, Encoding),
+ StLimit = if
+ CharsLimit < 0 ->
+ CharsLimit;
+ true ->
+ %% Reserve one third for the stacktrace.
+ CharsLimit div 3
+ end,
+ St = format_stacktrace1(S, Trace, FormatFun, StackFun, Encoding, StLimit),
+ Lim = sub(sub(CharsLimit, exited(Class), latin1), St, Encoding),
+ Expl0 = explain_reason(Term, Class, Trace1, FormatFun, S, Encoding, Lim),
FormatString = case Encoding of
latin1 -> "~s~s";
_ -> "~s~ts"
end,
Expl = io_lib:fwrite(FormatString, [exited(Class), Expl0]),
- case format_stacktrace1(S, Trace, FormatFun, StackFun, Encoding) of
+ case St of
[] -> Expl;
- Stack -> [Expl, $\n, Stack]
+ _ -> [Expl, $\n, St]
end.
%% -> iolist() (no \n at end)
@@ -63,7 +77,8 @@ format_stacktrace(I, StackTrace, StackFun, FormatFun, Encoding)
when is_integer(I), I >= 1, is_function(StackFun, 3),
is_function(FormatFun, 2) ->
S = n_spaces(I-1),
- format_stacktrace1(S, StackTrace, FormatFun, StackFun, Encoding).
+ FF = wrap_format_fun_2(FormatFun),
+ format_stacktrace1(S, StackTrace, FF, StackFun, Encoding, -1).
%% -> iolist() (no \n at end)
format_call(I, ForMForFun, As, FormatFun) ->
@@ -72,7 +87,8 @@ format_call(I, ForMForFun, As, FormatFun) ->
%% -> iolist() | unicode:charlist() (no \n at end)
format_call(I, ForMForFun, As, FormatFun, Enc)
when is_integer(I), I >= 1, is_list(As), is_function(FormatFun, 2) ->
- format_call("", n_spaces(I-1), ForMForFun, As, FormatFun, Enc).
+ FF = wrap_format_fun_2(FormatFun),
+ format_call("", n_spaces(I-1), ForMForFun, As, FF, Enc).
%% -> iolist() (no \n at end)
format_fun(Fun) ->
@@ -94,6 +110,9 @@ format_fun(Fun, Enc) when is_function(Fun) ->
mfa_to_string(M, F, A, Enc)
end.
+wrap_format_fun_2(FormatFun) ->
+ fun(T, I1, CL) -> {FormatFun(T, I1), CL} end.
+
analyze_exception(error, Term, Stack) ->
case {is_stacktrace(Stack), Stack, Term} of
{true, [{_,_,As,_}=MFAL|MFAs], function_clause} when is_list(As) ->
@@ -127,82 +146,83 @@ is_stacktrace(_) ->
false.
%% ERTS exit codes (some of them are also returned by erl_eval):
-explain_reason(badarg, error, [], _PF, _S, _Enc) ->
+explain_reason(badarg, error, [], _PF, _S, _Enc, _CL) ->
<<"bad argument">>;
-explain_reason({badarg,V}, error=Cl, [], PF, S, _Enc) -> % orelse, andalso
- format_value(V, <<"bad argument: ">>, Cl, PF, S);
-explain_reason(badarith, error, [], _PF, _S, _Enc) ->
+explain_reason({badarg,V}, error=Cl, [], PF, S, _Enc, CL) -> % orelse, andalso
+ format_value(V, <<"bad argument: ">>, Cl, PF, S, CL);
+explain_reason(badarith, error, [], _PF, _S, _Enc, _CL) ->
<<"an error occurred when evaluating an arithmetic expression">>;
-explain_reason({badarity,{Fun,As}}, error, [], _PF, _S, Enc)
+explain_reason({badarity,{Fun,As}}, error, [], _PF, _S, Enc, _CL)
when is_function(Fun) ->
%% Only the arity is displayed, not the arguments As.
io_lib:fwrite(<<"~ts called with ~s">>,
[format_fun(Fun, Enc), argss(length(As))]);
-explain_reason({badfun,Term}, error=Cl, [], PF, S, _Enc) ->
- format_value(Term, <<"bad function ">>, Cl, PF, S);
-explain_reason({badmatch,Term}, error=Cl, [], PF, S, _Enc) ->
+explain_reason({badfun,Term}, error=Cl, [], PF, S, _Enc, CL) ->
+ format_value(Term, <<"bad function ">>, Cl, PF, S, CL);
+explain_reason({badmatch,Term}, error=Cl, [], PF, S, _Enc, CL) ->
Str = <<"no match of right hand side value ">>,
- format_value(Term, Str, Cl, PF, S);
-explain_reason({case_clause,V}, error=Cl, [], PF, S, _Enc) ->
+ format_value(Term, Str, Cl, PF, S, CL);
+explain_reason({case_clause,V}, error=Cl, [], PF, S, _Enc, CL) ->
%% "there is no case clause with a true guard sequence and a
%% pattern matching..."
- format_value(V, <<"no case clause matching ">>, Cl, PF, S);
-explain_reason(function_clause, error, [{F,A}], _PF, _S, _Enc) ->
+ format_value(V, <<"no case clause matching ">>, Cl, PF, S, CL);
+explain_reason(function_clause, error, [{F,A}], _PF, _S, _Enc, _CL) ->
%% 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,Loc}], PF, S, Enc) ->
+explain_reason(function_clause, error=Cl, [{M,F,As,Loc}], PF, S, Enc, CL) ->
Str = <<"no function clause matching ">>,
- [format_errstr_call(Str, Cl, {M,F}, As, PF, S, Enc),$\s|location(Loc)];
-explain_reason(if_clause, error, [], _PF, _S, _Enc) ->
+ [format_errstr_call(Str, Cl, {M,F}, As, PF, S, Enc, CL),$\s|location(Loc)];
+explain_reason(if_clause, error, [], _PF, _S, _Enc, _CL) ->
<<"no true branch found when evaluating an if expression">>;
-explain_reason(noproc, error, [], _PF, _S, _Enc) ->
+explain_reason(noproc, error, [], _PF, _S, _Enc, _CL) ->
<<"no such process or port">>;
-explain_reason(notalive, error, [], _PF, _S, _Enc) ->
+explain_reason(notalive, error, [], _PF, _S, _Enc, _CL) ->
<<"the node cannot be part of a distributed system">>;
-explain_reason(system_limit, error, [], _PF, _S, _Enc) ->
+explain_reason(system_limit, error, [], _PF, _S, _Enc, _CL) ->
<<"a system limit has been reached">>;
-explain_reason(timeout_value, error, [], _PF, _S, _Enc) ->
+explain_reason(timeout_value, error, [], _PF, _S, _Enc, _CL) ->
<<"bad receive timeout value">>;
-explain_reason({try_clause,V}, error=Cl, [], PF, S, _Enc) ->
+explain_reason({try_clause,V}, error=Cl, [], PF, S, _Enc, CL) ->
%% "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, Enc) ->
+ format_value(V, <<"no try clause matching ">>, Cl, PF, S, CL);
+explain_reason(undef, error, [{M,F,A,_}], _PF, _S, Enc, _CL) ->
%% Only the arity is displayed, not the arguments, if there are any.
io_lib:fwrite(<<"undefined function ~ts">>,
[mfa_to_string(M, F, n_args(A), Enc)]);
-explain_reason({shell_undef,F,A,_}, error, [], _PF, _S, Enc) ->
+explain_reason({shell_undef,F,A,_}, error, [], _PF, _S, Enc, _CL) ->
%% Give nicer reports for undefined shell functions
%% (but not when the user actively calls shell_default:F(...)).
FS = to_string(F, Enc),
io_lib:fwrite(<<"undefined shell command ~ts/~w">>, [FS, n_args(A)]);
%% Exit codes returned by erl_eval only:
-explain_reason({argument_limit,_Fun}, error, [], _PF, _S, _Enc) ->
+explain_reason({argument_limit,_Fun}, error, [], _PF, _S, _Enc, _CL) ->
io_lib:fwrite(<<"limit of number of arguments to interpreted function"
" exceeded">>, []);
-explain_reason({bad_filter,V}, error=Cl, [], PF, S, _Enc) ->
- format_value(V, <<"bad filter ">>, Cl, PF, S);
-explain_reason({bad_generator,V}, error=Cl, [], PF, S, _Enc) ->
- format_value(V, <<"bad generator ">>, Cl, PF, S);
-explain_reason({unbound,V}, error, [], _PF, _S, _Enc) ->
+explain_reason({bad_filter,V}, error=Cl, [], PF, S, _Enc, CL) ->
+ format_value(V, <<"bad filter ">>, Cl, PF, S, CL);
+explain_reason({bad_generator,V}, error=Cl, [], PF, S, _Enc, CL) ->
+ format_value(V, <<"bad generator ">>, Cl, PF, S, CL);
+explain_reason({unbound,V}, error, [], _PF, _S, _Enc, _CL) ->
io_lib:fwrite(<<"variable ~w is unbound">>, [V]);
%% Exit codes local to the shell module (restricted shell):
-explain_reason({restricted_shell_bad_return, V}, exit=Cl, [], PF, S, _Enc) ->
+explain_reason({restricted_shell_bad_return, V}, exit=Cl, [], PF, S, _Enc, CL) ->
Str = <<"restricted shell module returned bad value ">>,
- format_value(V, Str, Cl, PF, S);
+ format_value(V, Str, Cl, PF, S, CL);
explain_reason({restricted_shell_disallowed,{ForMF,As}},
- exit=Cl, [], PF, S, Enc) ->
+ exit=Cl, [], PF, S, Enc, CL) ->
%% ForMF can be a fun, but not a shell fun.
Str = <<"restricted shell does not allow ">>,
- format_errstr_call(Str, Cl, ForMF, As, PF, S, Enc);
-explain_reason(restricted_shell_started, exit, [], _PF, _S, _Enc) ->
+ format_errstr_call(Str, Cl, ForMF, As, PF, S, Enc, CL);
+explain_reason(restricted_shell_started, exit, [], _PF, _S, _Enc, _CL) ->
<<"restricted shell starts now">>;
-explain_reason(restricted_shell_stopped, exit, [], _PF, _S, _Enc) ->
+explain_reason(restricted_shell_stopped, exit, [], _PF, _S, _Enc, _CL) ->
<<"restricted shell stopped">>;
%% Other exit code:
-explain_reason(Reason, Class, [], PF, S, _Enc) ->
- PF(Reason, (iolist_size(S)+1) + exited_size(Class)).
+explain_reason(Reason, Class, [], PF, S, _Enc, CL) ->
+ {L, _} = PF(Reason, (iolist_size(S)+1) + exited_size(Class), CL),
+ L.
n_args(A) when is_integer(A) ->
A;
@@ -218,29 +238,33 @@ argss(2) ->
argss(I) ->
io_lib:fwrite(<<"~w arguments">>, [I]).
-format_stacktrace1(S0, Stack0, PF, SF, Enc) ->
+format_stacktrace1(S0, Stack0, PF, SF, Enc, CL) ->
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, Enc).
-
-format_stacktrace2(S, [{M,F,A,L}|Fs], N, PF, Enc) when is_integer(A) ->
- [io_lib:fwrite(<<"~s~s ~ts ~ts">>,
- [sep(N, S), origin(N, M, F, A),
- mfa_to_string(M, F, A, Enc),
- location(L)])
- | format_stacktrace2(S, Fs, N + 1, PF, Enc)];
-format_stacktrace2(S, [{M,F,As,_}|Fs], N, PF, Enc) when is_list(As) ->
+ format_stacktrace2(S, Stack, 1, PF, Enc, CL).
+
+format_stacktrace2(_S, _Stack, _N, _PF, _Enc, _CL=0) ->
+ [];
+format_stacktrace2(S, [{M,F,A,L}|Fs], N, PF, Enc, CL) when is_integer(A) ->
+ Cs = io_lib:fwrite(<<"~s~s ~ts ~ts">>,
+ [sep(N, S), origin(N, M, F, A),
+ mfa_to_string(M, F, A, Enc),
+ location(L)]),
+ CL1 = sub(CL, Cs, Enc),
+ [Cs | format_stacktrace2(S, Fs, N + 1, PF, Enc, CL1)];
+format_stacktrace2(S, [{M,F,As,_}|Fs], N, PF, Enc, CL) when is_list(As) ->
A = length(As),
CalledAs = [S,<<" called as ">>],
- C = format_call("", CalledAs, {M,F}, As, PF, Enc),
- [io_lib:fwrite(<<"~s~s ~ts\n~s~ts">>,
- [sep(N, S), origin(N, M, F, A),
- mfa_to_string(M, F, A, Enc),
- CalledAs, C])
- | format_stacktrace2(S, Fs, N + 1, PF, Enc)];
-format_stacktrace2(_S, [], _N, _PF, _Enc) ->
+ C = format_call("", CalledAs, {M,F}, As, PF, Enc, CL),
+ Cs = io_lib:fwrite(<<"~s~s ~ts\n~s~ts">>,
+ [sep(N, S), origin(N, M, F, A),
+ mfa_to_string(M, F, A, Enc),
+ CalledAs, C]),
+ CL1 = sub(CL, Enc, Cs),
+ [Cs | format_stacktrace2(S, Fs, N + 1, PF, Enc, CL1)];
+format_stacktrace2(_S, [], _N, _PF, _Enc, _CL) ->
"".
location(L) ->
@@ -264,22 +288,26 @@ origin(1, M, F, A) ->
origin(_N, _M, _F, _A) ->
<<"in call from">>.
-format_errstr_call(ErrStr, Class, ForMForFun, As, PF, Pre0, Enc) ->
+format_errstr_call(ErrStr, Class, ForMForFun, As, PF, Pre0, Enc, CL) ->
Pre1 = [Pre0 | n_spaces(exited_size(Class))],
- format_call(ErrStr, Pre1, ForMForFun, As, PF, Enc).
+ format_call(ErrStr, Pre1, ForMForFun, As, PF, Enc, CL).
format_call(ErrStr, Pre1, ForMForFun, As, PF, Enc) ->
+ format_call(ErrStr, Pre1, ForMForFun, As, PF, Enc, -1).
+
+format_call(ErrStr, Pre1, ForMForFun, As, PF, Enc, CL) ->
Arity = length(As),
[ErrStr |
case is_op(ForMForFun, Arity) of
{yes,Op} ->
- format_op(ErrStr, Pre1, Op, As, PF, Enc);
+ format_op(ErrStr, Pre1, Op, As, PF, Enc, CL);
no ->
MFs = mf_to_string(ForMForFun, Arity, Enc),
I1 = string:length([Pre1,ErrStr|MFs]),
- S1 = pp_arguments(PF, As, I1, Enc),
- S2 = pp_arguments(PF, As, string:length([Pre1|MFs]), Enc),
- Long = count_nl(pp_arguments(PF, [a2345,b2345], I1, Enc)) > 0,
+ S1 = pp_arguments(PF, As, I1, Enc, CL),
+ S2 = pp_arguments(PF, As, string:length([Pre1|MFs]), Enc, CL),
+ S3 = pp_arguments(PF, [a2345,b2345], I1, Enc, CL),
+ Long = count_nl(S3) > 0,
case Long or (count_nl(S2) < count_nl(S1)) of
true ->
[$\n, Pre1, MFs, S2];
@@ -288,14 +316,15 @@ format_call(ErrStr, Pre1, ForMForFun, As, PF, Enc) ->
end
end].
-format_op(ErrStr, Pre, Op, [A1], PF, _Enc) ->
+format_op(ErrStr, Pre, Op, [A1], PF, _Enc, CL) ->
OpS = io_lib:fwrite(<<"~s ">>, [Op]),
I1 = iolist_size([ErrStr,Pre,OpS]),
- [OpS | PF(A1, I1+1)];
-format_op(ErrStr, Pre, Op, [A1, A2], PF, Enc) ->
+ {S, _} = PF(A1, I1+1, CL),
+ [OpS | S];
+format_op(ErrStr, Pre, Op, [A1, A2], PF, Enc, CL) ->
I1 = iolist_size([ErrStr,Pre]),
- S1 = PF(A1, I1+1),
- S2 = PF(A2, I1+1),
+ {S1, CL1} = PF(A1, I1+1, CL),
+ {S2, _} = PF(A2, I1+1, CL1),
OpS = atom_to_list(Op),
Pre1 = [$\n | n_spaces(I1)],
case count_nl(S1) > 0 of
@@ -304,26 +333,28 @@ format_op(ErrStr, Pre, Op, [A1, A2], PF, Enc) ->
false ->
OpS2 = io_lib:fwrite(<<" ~s ">>, [Op]),
Size1 = iolist_size([ErrStr,Pre|OpS2]),
- {Size2,S1_2} = size(Enc, S1),
- S2_2 = PF(A2, Size1+Size2+1),
+ Size2 = size(Enc, S1),
+ {S2_2, _} = PF(A2, Size1+Size2+1, CL1),
case count_nl(S2) < count_nl(S2_2) of
true ->
- [S1_2,Pre1,OpS,Pre1|S2];
+ [S1,Pre1,OpS,Pre1|S2];
false ->
- [S1_2,OpS2|S2_2]
+ [S1,OpS2|S2_2]
end
end.
-pp_arguments(PF, As, I, Enc) ->
+pp_arguments(PF, As, I, Enc, CL) ->
case {As, printable_list(Enc, As)} of
{[Int | T], true} ->
L = integer_to_list(Int),
Ll = length(L),
A = list_to_atom(lists:duplicate(Ll, $a)),
- S0 = unicode:characters_to_list(PF([A | T], I+1), Enc),
- brackets_to_parens([$[,L,string:slice(S0, 1+Ll)], Enc);
+ {S0, _} = PF([A | T], I+1, CL),
+ S = unicode:characters_to_list(S0, Enc),
+ brackets_to_parens([$[,L,string:slice(S, 1+Ll)], Enc);
_ ->
- brackets_to_parens(PF(As, I+1), Enc)
+ {S, _CL1} = PF(As, I+1, CL),
+ brackets_to_parens(S, Enc)
end.
brackets_to_parens(S, Enc) ->
@@ -361,12 +392,12 @@ mf_to_string(F, _A, Enc) ->
FS = to_string(F, Enc),
io_lib:fwrite(<<"~ts">>, [FS]).
-format_value(V, ErrStr, Class, PF, S) ->
+format_value(V, ErrStr, Class, PF, S, CL) ->
Pre1Sz = exited_size(Class),
- S1 = PF(V, Pre1Sz + iolist_size([S, ErrStr])+1),
+ {S1, _} = PF(V, Pre1Sz + iolist_size([S, ErrStr]) + 1, CL),
[ErrStr | case count_nl(S1) of
N1 when N1 > 1 ->
- S2 = PF(V, iolist_size(S) + 1 + Pre1Sz),
+ {S2, _} = PF(V, iolist_size(S) + 1 + Pre1Sz, CL),
case count_nl(S2) < N1 of
true ->
[$\n, S, n_spaces(Pre1Sz) | S2];
@@ -413,9 +444,17 @@ to_string(A, latin1) ->
to_string(A, _) ->
io_lib:write_atom(A).
+%% Make sure T does change sign.
+sub(T, _, _Enc) when T < 0 -> T;
+sub(T, S, Enc) ->
+ sub(T, size(Enc, S)).
+
+sub(T, Sz) when T >= Sz ->
+ T - Sz;
+sub(_T, _Sz) ->
+ 0.
+
size(latin1, S) ->
- {iolist_size(S),S};
-size(_, S0) ->
- S = unicode:characters_to_list(S0, unicode),
- true = is_list(S),
- {string:length(S),S}.
+ iolist_size(S);
+size(_, S) ->
+ string:length(S).
diff --git a/lib/stdlib/src/erl_eval.erl b/lib/stdlib/src/erl_eval.erl
index 2066b2f60f..aa809ab05c 100644
--- a/lib/stdlib/src/erl_eval.erl
+++ b/lib/stdlib/src/erl_eval.erl
@@ -501,13 +501,13 @@ find_maxline(LC) ->
hide_calls(LC, MaxLine) ->
LineId0 = MaxLine + 1,
- {NLC, _, D} = hide(LC, LineId0, dict:new()),
+ {NLC, _, D} = hide(LC, LineId0, maps:new()),
{NLC, D}.
%% v/1 and local calls are hidden.
hide({value,L,V}, Id, D) ->
A = erl_anno:new(Id),
- {{atom,A,ok}, Id+1, dict:store(Id, {value,L,V}, D)};
+ {{atom,A,ok}, Id+1, maps:put(Id, {value,L,V}, D)};
hide({call,L,{atom,_,N}=Atom,Args}, Id0, D0) ->
{NArgs, Id, D} = hide(Args, Id0, D0),
C = case erl_internal:bif(N, length(Args)) of
@@ -517,7 +517,7 @@ hide({call,L,{atom,_,N}=Atom,Args}, Id0, D0) ->
A = erl_anno:new(Id),
{call,A,{remote,L,{atom,L,m},{atom,L,f}},NArgs}
end,
- {C, Id+1, dict:store(Id, {call,Atom}, D)};
+ {C, Id+1, maps:put(Id, {call,Atom}, D)};
hide(T0, Id0, D0) when is_tuple(T0) ->
{L, Id, D} = hide(tuple_to_list(T0), Id0, D0),
{list_to_tuple(L), Id, D};
@@ -532,7 +532,7 @@ unhide_calls({atom,A,ok}=E, MaxLine, D) ->
L = erl_anno:line(A),
if
L > MaxLine ->
- dict:fetch(L, D);
+ map_get(L, D);
true ->
E
end;
@@ -540,7 +540,7 @@ unhide_calls({call,A,{remote,L,{atom,L,m},{atom,L,f}}=F,Args}, MaxLine, D) ->
Line = erl_anno:line(A),
if
Line > MaxLine ->
- {call,Atom} = dict:fetch(Line, D),
+ {call,Atom} = map_get(Line, D),
{call,L,Atom,unhide_calls(Args, MaxLine, D)};
true ->
{call,A,F,unhide_calls(Args, MaxLine, D)}
@@ -1163,9 +1163,19 @@ match1({map,_,Fs}, #{}=Map, Bs, BBs) ->
match1({map,_,_}, _, _Bs, _BBs) ->
throw(nomatch);
match1({bin, _, Fs}, <<_/bitstring>>=B, Bs0, BBs) ->
- eval_bits:match_bits(Fs, B, Bs0, BBs,
- match_fun(BBs),
- fun(E, Bs) -> expr(E, Bs, none, none, none) end);
+ EvalFun = fun(E, Bs) ->
+ case erl_lint:is_guard_expr(E) of
+ true -> ok;
+ false -> throw(invalid)
+ end,
+ try
+ expr(E, Bs, none, none, none)
+ catch
+ error:{unbound, _} ->
+ throw(invalid)
+ end
+ end,
+ eval_bits:match_bits(Fs, B, Bs0, BBs, match_fun(BBs), EvalFun);
match1({bin,_,_}, _, _Bs, _BBs) ->
throw(nomatch);
match1({op,_,'++',{nil,_},R}, Term, Bs, BBs) ->
diff --git a/lib/stdlib/src/erl_expand_records.erl b/lib/stdlib/src/erl_expand_records.erl
index d7bd15d9db..5351490b1a 100644
--- a/lib/stdlib/src/erl_expand_records.erl
+++ b/lib/stdlib/src/erl_expand_records.erl
@@ -797,9 +797,13 @@ is_simple_val(Val) ->
pattern_bin(Es0, St) ->
foldr(fun (E, Acc) -> pattern_element(E, Acc) end, {[],St}, Es0).
-pattern_element({bin_element,Line,Expr0,Size,Type}, {Es,St0}) ->
+pattern_element({bin_element,Line,Expr0,Size0,Type}, {Es,St0}) ->
{Expr,St1} = pattern(Expr0, St0),
- {[{bin_element,Line,Expr,Size,Type} | Es],St1}.
+ {Size,St2} = case Size0 of
+ default -> {Size0,St1};
+ _ -> expr(Size0, St1)
+ end,
+ {[{bin_element,Line,Expr,Size,Type} | Es],St2}.
%% expr_bin([Element], State) -> {[Element],State}.
diff --git a/lib/stdlib/src/erl_internal.erl b/lib/stdlib/src/erl_internal.erl
index 939abaff00..f5059ac710 100644
--- a/lib/stdlib/src/erl_internal.erl
+++ b/lib/stdlib/src/erl_internal.erl
@@ -245,11 +245,14 @@ bif(M, F, A) when is_atom(M), is_atom(F), is_integer(A) -> false.
bif(abs, 1) -> true;
bif(apply, 2) -> true;
bif(apply, 3) -> true;
+bif(atom_to_binary, 1) -> true;
bif(atom_to_binary, 2) -> true;
bif(atom_to_list, 1) -> true;
bif(binary_part, 2) -> true;
bif(binary_part, 3) -> true;
+bif(binary_to_atom, 1) -> true;
bif(binary_to_atom, 2) -> true;
+bif(binary_to_existing_atom, 1) -> true;
bif(binary_to_existing_atom, 2) -> true;
bif(binary_to_integer, 1) -> true;
bif(binary_to_integer, 2) -> true;
@@ -383,8 +386,16 @@ bif(spawn_link, 1) -> true;
bif(spawn_link, 2) -> true;
bif(spawn_link, 3) -> true;
bif(spawn_link, 4) -> true;
+bif(spawn_request, 1) -> true;
+bif(spawn_request, 2) -> true;
+bif(spawn_request, 3) -> true;
+bif(spawn_request, 4) -> true;
+bif(spawn_request, 5) -> true;
+bif(spawn_request_abandon, 1) -> true;
bif(spawn_monitor, 1) -> true;
+bif(spawn_monitor, 2) -> true;
bif(spawn_monitor, 3) -> true;
+bif(spawn_monitor, 4) -> true;
bif(spawn_opt, 2) -> true;
bif(spawn_opt, 3) -> true;
bif(spawn_opt, 4) -> true;
@@ -393,6 +404,8 @@ bif(split_binary, 2) -> true;
bif(statistics, 1) -> true;
bif(term_to_binary, 1) -> true;
bif(term_to_binary, 2) -> true;
+bif(term_to_iovec, 1) -> true;
+bif(term_to_iovec, 2) -> true;
bif(throw, 1) -> true;
bif(time, 0) -> true;
bif(tl, 1) -> true;
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 54b0fbd999..5163b0df1d 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -1,4 +1,4 @@
-%% -*- erlang-indent-level: 4 -*-
+%%% -*- erlang-indent-level: 4 -*-
%%
%% %CopyrightBegin%
%%
@@ -33,6 +33,10 @@
-import(lists, [member/2,map/2,foldl/3,foldr/3,mapfoldl/3,all/2,reverse/1]).
+%% Removed functions
+
+-removed([{modify_line,2,"use erl_parse:map_anno/2 instead"}]).
+
%% bool_option(OnOpt, OffOpt, Default, Options) -> boolean().
%% value_option(Flag, Default, Options) -> Value.
%% value_option(Flag, Default, OnOpt, OnVal, OffOpt, OffVal, Options) ->
@@ -81,17 +85,19 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->
-type module_or_mfa() :: module() | mfa().
+-type gexpr_context() :: 'guard' | 'bin_seg_size' | 'map_key'.
+
-record(typeinfo, {attr, line}).
%% Usage of records, functions, and imports. The variable table, which
%% is passed on as an argument, holds the usage of variables.
-record(usage, {
- calls = dict:new(), %Who calls who
+ calls = maps:new(), %Who calls who
imported = [], %Actually imported functions
- used_records = sets:new() %Used record definitions
- :: sets:set(atom()),
- used_types = dict:new() %Used type definitions
- :: dict:dict(ta(), line())
+ used_records = gb_sets:new() %Used record definitions
+ :: gb_sets:set(atom()),
+ used_types = maps:new() %Used type definitions
+ :: #{ta() := line()}
}).
@@ -104,8 +110,8 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->
exports=gb_sets:empty() :: gb_sets:set(fa()),%Exports
imports=[] :: orddict:orddict(fa(), module()),%Imports
compile=[], %Compile flags
- records=dict:new() %Record definitions
- :: dict:dict(atom(), {line(),Fields :: term()}),
+ records=maps:new() %Record definitions
+ :: #{atom() => {line(),Fields :: term()}},
locals=gb_sets:empty() %All defined functions (prescanned)
:: gb_sets:set(fa()),
no_auto=gb_sets:empty() %Functions explicitly not autoimported
@@ -131,17 +137,20 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->
xqlc= false :: boolean(), %true if qlc.hrl included
called= [] :: [{fa(),line()}], %Called functions
usage = #usage{} :: #usage{},
- specs = dict:new() %Type specifications
- :: dict:dict(mfa(), line()),
- callbacks = dict:new() %Callback types
- :: dict:dict(mfa(), line()),
- optional_callbacks = dict:new() %Optional callbacks
- :: dict:dict(mfa(), line()),
- types = dict:new() %Type definitions
- :: dict:dict(ta(), #typeinfo{}),
+ specs = maps:new() %Type specifications
+ :: #{mfa() => line()},
+ callbacks = maps:new() %Callback types
+ :: #{mfa() => line()},
+ optional_callbacks = maps:new() %Optional callbacks
+ :: #{mfa() => line()},
+ types = maps:new() %Type definitions
+ :: #{ta() => #typeinfo{}},
exp_types=gb_sets:empty() %Exported types
:: gb_sets:set(ta()),
- in_try_head=false :: boolean() %In a try head.
+ in_try_head=false :: boolean(), %In a try head.
+ bvt = none :: 'none' | [any()], %Variables in binary pattern
+ gexpr_context = guard %Context of guard expression
+ :: gexpr_context()
}).
-type lint_state() :: #lint{}.
@@ -183,6 +192,14 @@ format_error({invalid_deprecated,D}) ->
format_error({bad_deprecated,{F,A}}) ->
io_lib:format("deprecated function ~tw/~w undefined or not exported",
[F,A]);
+format_error({invalid_removed,D}) ->
+ io_lib:format("badly formed removed attribute ~tw", [D]);
+format_error({bad_removed,{F,A}}) when F =:= '_'; A =:= '_' ->
+ io_lib:format("at least one function matching ~tw/~w is still exported",
+ [F,A]);
+format_error({bad_removed,{F,A}}) ->
+ io_lib:format("removed function ~tw/~w is still exported",
+ [F,A]);
format_error({bad_nowarn_unused_function,{F,A}}) ->
io_lib:format("function ~tw/~w undefined", [F,A]);
format_error({bad_nowarn_bif_clash,{F,A}}) ->
@@ -231,18 +248,18 @@ format_error({redefine_bif_import,{F,A}}) ->
format_error({deprecated, MFA, ReplacementMFA, Rel}) ->
io_lib:format("~s is deprecated and will be removed in ~s; use ~s",
[format_mfa(MFA), Rel, format_mfa(ReplacementMFA)]);
-format_error({deprecated, {M1, F1, A1}, String}) when is_list(String) ->
- io_lib:format("~p:~p/~p: ~s", [M1, F1, A1, String]);
+format_error({deprecated, MFA, String}) when is_list(String) ->
+ io_lib:format("~s is deprecated; ~s", [format_mfa(MFA), String]);
format_error({deprecated_type, {M1, F1, A1}, String}) when is_list(String) ->
- io_lib:format("~p:~p~s: ~s", [M1, F1, gen_type_paren(A1), String]);
+ io_lib:format("the type ~p:~p~s is deprecated; ~s",
+ [M1, F1, gen_type_paren(A1), String]);
format_error({removed, MFA, ReplacementMFA, Rel}) ->
io_lib:format("call to ~s will fail, since it was removed in ~s; "
"use ~s", [format_mfa(MFA), Rel, format_mfa(ReplacementMFA)]);
format_error({removed, MFA, String}) when is_list(String) ->
- io_lib:format("~s: ~s", [format_mfa(MFA), String]);
-format_error({removed_type, MNA, ReplacementMNA, Rel}) ->
- io_lib:format("the type ~s was removed in ~s; use ~s instead",
- [format_mna(MNA), Rel, format_mna(ReplacementMNA)]);
+ io_lib:format("~s is removed; ~s", [format_mfa(MFA), String]);
+format_error({removed_type, MNA, String}) ->
+ io_lib:format("the type ~s is removed; ~s", [format_mna(MNA), String]);
format_error({obsolete_guard, {F, A}}) ->
io_lib:format("~p/~p obsolete (use is_~p/~p)", [F, A, F, A]);
format_error({obsolete_guard_overridden,Test}) ->
@@ -313,6 +330,13 @@ format_error(bittype_unit) ->
"a bit unit size must not be specified unless a size is specified too";
format_error(illegal_bitsize) ->
"illegal bit size";
+format_error({illegal_bitsize_local_call, {F,A}}) ->
+ io_lib:format("call to local/imported function ~tw/~w is illegal in a size "
+ "expression for a binary segment",
+ [F,A]);
+format_error(non_integer_bitsize) ->
+ "a size expression in a pattern evaluates to a non-integer value; "
+ "this pattern cannot possibly match";
format_error(unsized_binary_not_at_end) ->
"a binary field without size is only allowed at the end of a binary pattern";
format_error(typed_literal_string) ->
@@ -591,7 +615,7 @@ start(File, Opts) ->
Enabled = ordsets:from_list(Enabled1),
Calls = case ordsets:is_element(unused_function, Enabled) of
true ->
- dict:from_list([{{module_info,1},pseudolocals()}]);
+ maps:from_list([{{module_info,1},pseudolocals()}]);
false ->
undefined
end,
@@ -647,7 +671,14 @@ pack_warnings(Ws) ->
add_error(E, St) -> add_lint_error(E, St#lint.file, St).
-add_error(Anno, E, St) ->
+add_error(Anno, E0, #lint{gexpr_context=Context}=St) ->
+ E = case {E0,Context} of
+ {illegal_guard_expr,bin_seg_size} ->
+ illegal_bitsize;
+ {{illegal_guard_local_call,FA},bin_seg_size} ->
+ {illegal_bitsize_local_call,FA};
+ {_,_} -> E0
+ end,
{File,Location} = loc(Anno, St),
add_lint_error({Location,erl_lint,E}, File, St).
@@ -918,7 +949,8 @@ post_traversal_check(Forms, St0) ->
StE = check_unused_records(Forms, StD),
StF = check_local_opaque_types(StE),
StG = check_dialyzer_attribute(Forms, StF),
- check_callback_information(StG).
+ StH = check_callback_information(StG),
+ check_removed(Forms, StH).
%% check_behaviour(State0) -> State
%% Check that the behaviour attribute is valid.
@@ -1030,7 +1062,7 @@ check_deprecated(Forms, St0) ->
true -> St0#lint.defined;
false -> St0#lint.exports
end,
- X = gb_sets:to_list(Exports),
+ X = ignore_predefined_funcs(gb_sets:to_list(Exports)),
#lint{module = Mod} = St0,
Bad = [{E,L} || {attribute, L, deprecated, Depr} <- Forms,
D <- lists:flatten([Depr]),
@@ -1074,7 +1106,80 @@ depr_fa(F, A, _X, _Mod) ->
deprecated_flag(next_version) -> true;
deprecated_flag(next_major_release) -> true;
deprecated_flag(eventually) -> true;
-deprecated_flag(_) -> false.
+deprecated_flag(String) -> deprecated_desc(String).
+
+deprecated_desc([Char | Str]) when is_integer(Char) -> deprecated_desc(Str);
+deprecated_desc([]) -> true;
+deprecated_desc(_) -> false.
+
+%% check_removed(Forms, State0) -> State
+
+check_removed(Forms, St0) ->
+ %% Get the correct list of exported functions.
+ Exports = case member(export_all, St0#lint.compile) of
+ true -> St0#lint.defined;
+ false -> St0#lint.exports
+ end,
+ X = ignore_predefined_funcs(gb_sets:to_list(Exports)),
+ #lint{module = Mod} = St0,
+ Bad = [{E,L} || {attribute, L, removed, Removed} <- Forms,
+ R <- lists:flatten([Removed]),
+ E <- removed_cat(R, X, Mod)],
+ foldl(fun ({E,L}, St1) ->
+ add_error(L, E, St1)
+ end, St0, Bad).
+
+removed_cat({F, A, Desc}=R, X, Mod) ->
+ case removed_desc(Desc) of
+ false -> [{invalid_removed,R}];
+ true -> removed_fa(F, A, X, Mod)
+ end;
+removed_cat({F, A}, X, Mod) ->
+ removed_fa(F, A, X, Mod);
+removed_cat(module, X, Mod) ->
+ removed_fa('_', '_', X, Mod);
+removed_cat(R, _X, _Mod) ->
+ [{invalid_removed,R}].
+
+removed_fa('_', '_', X, _Mod) ->
+ case X of
+ [_|_] -> [{bad_removed,{'_','_'}}];
+ [] -> []
+ end;
+removed_fa(F, '_', X, _Mod) when is_atom(F) ->
+ %% Don't use this syntax for built-in functions.
+ case lists:filter(fun({F1,_}) -> F1 =:= F end, X) of
+ [_|_] -> [{bad_removed,{F,'_'}}];
+ _ -> []
+ end;
+removed_fa(F, A, X, Mod) when is_atom(F), is_integer(A), A >= 0 ->
+ case lists:member({F,A}, X) of
+ true ->
+ [{bad_removed,{F,A}}];
+ false ->
+ case erlang:is_builtin(Mod, F, A) of
+ true -> [{bad_removed,{F,A}}];
+ false -> []
+ end
+ end;
+removed_fa(F, A, _X, _Mod) ->
+ [{invalid_removed,{F,A}}].
+
+removed_desc([Char | Str]) when is_integer(Char) -> removed_desc(Str);
+removed_desc([]) -> true;
+removed_desc(_) -> false.
+
+%% Ignores functions added by erl_internal:add_predefined_functions/1
+ignore_predefined_funcs([{behaviour_info,1} | Fs]) ->
+ ignore_predefined_funcs(Fs);
+ignore_predefined_funcs([{module_info,0} | Fs]) ->
+ ignore_predefined_funcs(Fs);
+ignore_predefined_funcs([{module_info,1} | Fs]) ->
+ ignore_predefined_funcs(Fs);
+ignore_predefined_funcs([Other | Fs]) ->
+ [Other | ignore_predefined_funcs(Fs)];
+ignore_predefined_funcs([]) ->
+ [].
%% check_imports(Forms, State0) -> State
@@ -1134,7 +1239,7 @@ reached_functions([R|Rs], More0, Ref, Reached0) ->
true -> reached_functions(Rs, More0, Ref, Reached0);
false ->
Reached = gb_sets:add_element(R, Reached0), %It IS reached
- case dict:find(R, Ref) of
+ case maps:find(R, Ref) of
{ok,More} -> reached_functions(Rs, [More|More0], Ref, Reached);
error -> reached_functions(Rs, More0, Ref, Reached)
end
@@ -1157,10 +1262,10 @@ check_undefined_functions(#lint{called=Called0,defined=Def0}=St0) ->
check_undefined_types(#lint{usage=Usage,types=Def}=St0) ->
Used = Usage#usage.used_types,
- UTAs = dict:fetch_keys(Used),
- Undef = [{TA,dict:fetch(TA, Used)} ||
+ UTAs = maps:keys(Used),
+ Undef = [{TA,map_get(TA, Used)} ||
TA <- UTAs,
- not dict:is_key(TA, Def),
+ not is_map_key(TA, Def),
not is_default_type(TA)],
foldl(fun ({TA,L}, St) ->
add_error(L, {undefined_type,TA}, St)
@@ -1199,7 +1304,7 @@ check_untyped_records(Forms, St0) ->
case is_warn_enabled(untyped_record, St0) of
true ->
%% Use the names of all records *defined* in the module (not used)
- RecNames = dict:fetch_keys(St0#lint.records),
+ RecNames = maps:keys(St0#lint.records),
%% these are the records with field(s) containing type info
TRecNames = [Name ||
{attribute,_,record,{Name,Fields}} <- Forms,
@@ -1207,7 +1312,7 @@ check_untyped_records(Forms, St0) ->
(_) -> false
end, Fields)],
foldl(fun (N, St) ->
- {L, Fields} = dict:fetch(N, St0#lint.records),
+ {L, Fields} = map_get(N, St0#lint.records),
case Fields of
[] -> St; % exclude records with no fields
[_|_] -> add_warning(L, {untyped_record, N}, St)
@@ -1225,12 +1330,12 @@ check_unused_records(Forms, St0) ->
%% The check is a bit imprecise in that uses from unused
%% functions count.
Usage = St0#lint.usage,
- UsedRecords = sets:to_list(Usage#usage.used_records),
- URecs = foldl(fun (Used, Recs) ->
- dict:erase(Used, Recs)
- end, St0#lint.records, UsedRecords),
+ UsedRecords = Usage#usage.used_records,
+ URecs = gb_sets:fold(fun (Used, Recs) ->
+ maps:remove(Used, Recs)
+ end, St0#lint.records, UsedRecords),
Unused = [{Name,FileLine} ||
- {Name,{FileLine,_Fields}} <- dict:to_list(URecs),
+ {Name,{FileLine,_Fields}} <- maps:to_list(URecs),
element(1, loc(FileLine, St0)) =:= FirstFile],
foldl(fun ({N,L}, St) ->
add_warning(L, {unused_record, N}, St)
@@ -1242,27 +1347,26 @@ check_unused_records(Forms, St0) ->
check_callback_information(#lint{callbacks = Callbacks,
optional_callbacks = OptionalCbs,
defined = Defined} = St0) ->
- OptFun = fun({MFA, Line}, St) ->
- case dict:is_key(MFA, Callbacks) of
+ OptFun = fun(MFA, Line, St) ->
+ case is_map_key(MFA, Callbacks) of
true ->
St;
false ->
add_error(Line, {undefined_callback, MFA}, St)
end
end,
- St1 = lists:foldl(OptFun, St0, dict:to_list(OptionalCbs)),
+ St1 = maps:fold(OptFun, St0, OptionalCbs),
case gb_sets:is_member({behaviour_info, 1}, Defined) of
false -> St1;
true ->
- case dict:size(Callbacks) of
+ case map_size(Callbacks) of
0 -> St1;
_ ->
- CallbacksList = dict:to_list(Callbacks),
- FoldL =
- fun({Fa, Line}, St) ->
+ FoldFun =
+ fun(Fa, Line, St) ->
add_error(Line, {behaviour_info, Fa}, St)
end,
- lists:foldl(FoldL, St1, CallbacksList)
+ maps:fold(FoldFun, St1, Callbacks)
end
end.
@@ -1300,7 +1404,7 @@ export_type(Line, ETs, #lint{usage = Usage, exp_types = ETs0} = St0) ->
false ->
St2
end,
- {gb_sets:add_element(TA, E), dict:store(TA, Line, U), St}
+ {gb_sets:add_element(TA, E), maps:put(TA, Line, U), St}
end,
{ETs0,UTs0,St0}, ETs) of
{ETs1,UTs1,St1} ->
@@ -1430,7 +1534,7 @@ call_function(Line, F, A, #lint{usage=Usage0,called=Cd,func=Func,file=File}=St)
NA = {F,A},
Usage = case Cs of
undefined -> Usage0;
- _ -> Usage0#usage{calls=dict:append(Func, NA, Cs)}
+ _ -> Usage0#usage{calls=maps_prepend(Func, NA, Cs)}
end,
Anno = erl_anno:set_file(File, Line),
St#lint{called=[{NA,Anno}|Cd], usage=Usage}.
@@ -1541,7 +1645,7 @@ pattern({record_index,Line,Name,Field}, _Vt, _Old, _Bvt, St) ->
end),
{Vt1,[],St1};
pattern({record,Line,Name,Pfs}, Vt, Old, Bvt, St) ->
- case dict:find(Name, St#lint.records) of
+ case maps:find(Name, St#lint.records) of
{ok,{_Line,Fields}} ->
St1 = used_record(Name, St),
pattern_fields(Pfs, Name, Fields, Vt, Old, Bvt, St1);
@@ -1625,10 +1729,10 @@ reject_invalid_alias({tuple,_,Es1}, {tuple,_,Es2}, Vt, St) ->
reject_invalid_alias_list(Es1, Es2, Vt, St);
reject_invalid_alias({record,_,Name1,Pfs1}, {record,_,Name2,Pfs2}, Vt,
#lint{records=Recs}=St) ->
- case {dict:find(Name1, Recs),dict:find(Name2, Recs)} of
- {{ok,{_Line1,Fields1}},{ok,{_Line2,Fields2}}} ->
+ case Recs of
+ #{Name1 := {_Line1,Fields1}, Name2 := {_Line2,Fields2}} ->
reject_invalid_alias_rec(Pfs1, Pfs2, Fields1, Fields2, Vt, St);
- {_,_} ->
+ #{} ->
%% One or more non-existing records. (An error messages has
%% already been generated, so we are done here.)
St
@@ -1706,19 +1810,16 @@ is_pattern_expr_1({op,_Line,Op,A1,A2}) ->
is_pattern_expr_1(_Other) -> false.
pattern_map(Ps, Vt, Old, Bvt, St) ->
- foldl(fun
- ({map_field_assoc,L,_,_}, {Psvt,Bvt0,St0}) ->
- {Psvt,Bvt0,add_error(L, illegal_pattern, St0)};
- ({map_field_exact,L,K,V}, {Psvt,Bvt0,St0}) ->
- case is_valid_map_key(K) of
- true ->
- {Kvt,St1} = expr(K, Vt, St0),
- {Vvt,Bvt2,St2} = pattern(V, Vt, Old, Bvt, St1),
- {vtmerge_pat(vtmerge_pat(Kvt, Vvt), Psvt), vtmerge_pat(Bvt0, Bvt2), St2};
- false ->
- {Psvt,Bvt0,add_error(L, illegal_map_key, St0)}
- end
- end, {[],[],St}, Ps).
+ foldl(fun({map_field_assoc,L,_,_}, {Psvt,Bvt0,St0}) ->
+ {Psvt,Bvt0,add_error(L, illegal_pattern, St0)};
+ ({map_field_exact,_L,K,V}, {Psvt,Bvt0,St0}) ->
+ St1 = St0#lint{gexpr_context=map_key},
+ {Kvt,St2} = gexpr(K, Vt, St1),
+ {Vvt,Bvt2,St3} = pattern(V, Vt, Old, Bvt, St2),
+ {vtmerge_pat(vtmerge_pat(Kvt, Vvt), Psvt),
+ vtmerge_pat(Bvt0, Bvt2),
+ St3}
+ end, {[],[],St}, Ps).
%% pattern_bin([Element], VarTable, Old, BinVarTable, State) ->
%% {UpdVarTable,UpdBinVarTable,State}.
@@ -1787,21 +1888,41 @@ pat_bit_expr(P, _Old, _Bvt, St) ->
%% Check pattern size expression, only allow really valid sizes!
pat_bit_size(default, _Vt, _Bvt, St) -> {default,[],[],St};
-pat_bit_size({atom,_Line,all}, _Vt, _Bvt, St) -> {all,[],[],St};
pat_bit_size({var,Lv,V}, Vt0, Bvt0, St0) ->
{Vt,Bvt,St1} = pat_binsize_var(V, Lv, Vt0, Bvt0, St0),
{unknown,Vt,Bvt,St1};
-pat_bit_size(Size, _Vt, _Bvt, St) ->
+pat_bit_size(Size, Vt0, Bvt0, St0) ->
Line = element(2, Size),
- case is_pattern_expr(Size) of
- true ->
- case erl_eval:partial_eval(Size) of
- {integer,Line,I} -> {I,[],[],St};
- _Other -> {unknown,[],[],add_error(Line, illegal_bitsize, St)}
- end;
- false -> {unknown,[],[],add_error(Line, illegal_bitsize, St)}
+ case erl_eval:partial_eval(Size) of
+ {integer,Line,I} -> {I,[],[],St0};
+ Expr ->
+ %% The size is an expression using operators
+ %% and/or guard BIFs calls. If the expression
+ %% happens to evaluate to a non-integer value, the
+ %% pattern will fail to match.
+ St1 = St0#lint{bvt=Bvt0,gexpr_context=bin_seg_size},
+ {Vt,#lint{bvt=Bvt}=St2} = gexpr(Size, Vt0, St1),
+ St3 = St2#lint{bvt=none,gexpr_context=St0#lint.gexpr_context},
+ St = case is_bit_size_illegal(Expr) of
+ true ->
+ %% The size is a non-integer literal or a simple
+ %% expression that does not evaluate to an
+ %% integer value. Issue a warning.
+ add_warning(Line, non_integer_bitsize, St3);
+ false -> St3
+ end,
+ {unknown,Vt,Bvt,St}
end.
+is_bit_size_illegal({atom,_,_}) -> true;
+is_bit_size_illegal({bin,_,_}) -> true;
+is_bit_size_illegal({cons,_,_,_}) -> true;
+is_bit_size_illegal({float,_,_}) -> true;
+is_bit_size_illegal({map,_,_}) -> true;
+is_bit_size_illegal({nil,_}) -> true;
+is_bit_size_illegal({tuple,_,_}) -> true;
+is_bit_size_illegal(_) -> false.
+
%% expr_bin(Line, [Element], VarTable, State, CheckFun) -> {UpdVarTable,State}.
%% Check an expression group.
@@ -2067,7 +2188,7 @@ gexpr_list(Es, Vt, St) ->
Expr :: erl_parse:abstract_expr().
is_guard_test(E) ->
- is_guard_test2(E, {dict:new(),fun(_) -> false end}).
+ is_guard_test2(E, {maps:new(),fun(_) -> false end}).
%% is_guard_test(Expression, Forms) -> boolean().
is_guard_test(Expression, Forms) ->
@@ -2115,7 +2236,7 @@ is_guard_test2(G, Info) ->
%% is_guard_expr(Expression) -> boolean().
%% Test if an expression is a guard expression.
-is_guard_expr(E) -> is_gexpr(E, []).
+is_guard_expr(E) -> is_gexpr(E, {[],fun({_,_}) -> false end}).
is_gexpr({var,_L,_V}, _Info) -> true;
is_gexpr({char,_L,_C}, _Info) -> true;
@@ -2183,7 +2304,7 @@ is_map_fields([], _Info) -> true;
is_map_fields(_T, _Info) -> false.
is_gexpr_fields(Fs, L, Name, {RDs,_}=Info) ->
- IFs = case dict:find(Name, RDs) of
+ IFs = case maps:find(Name, RDs) of
{ok,{_Line,Fields}} -> Fs ++ init_fields(Fs, L, Fields);
error -> Fs
end,
@@ -2510,73 +2631,16 @@ is_valid_call(Call) ->
_ -> true
end.
-%% is_valid_map_key(K) -> true | false
-%% variables are allowed for patterns only at the top of the tree
-
-is_valid_map_key({var,_,_}) -> true;
-is_valid_map_key(K) -> is_valid_map_key_value(K).
-is_valid_map_key_value(K) ->
- case K of
- {var,_,_} -> false;
- {char,_,_} -> true;
- {integer,_,_} -> true;
- {float,_,_} -> true;
- {string,_,_} -> true;
- {nil,_} -> true;
- {atom,_,_} -> true;
- {cons,_,H,T} ->
- is_valid_map_key_value(H) andalso
- is_valid_map_key_value(T);
- {tuple,_,Es} ->
- foldl(fun(E,B) ->
- B andalso is_valid_map_key_value(E)
- end,true,Es);
- {map,_,Arg,Ps} ->
- % only check for value expressions to be valid
- % invalid map expressions are later checked in
- % core and kernel
- is_valid_map_key_value(Arg) andalso foldl(fun
- ({Tag,_,Ke,Ve},B) when Tag =:= map_field_assoc;
- Tag =:= map_field_exact ->
- B andalso is_valid_map_key_value(Ke)
- andalso is_valid_map_key_value(Ve);
- (_,_) -> false
- end,true,Ps);
- {map,_,Ps} ->
- foldl(fun
- ({Tag,_,Ke,Ve},B) when Tag =:= map_field_assoc;
- Tag =:= map_field_exact ->
- B andalso is_valid_map_key_value(Ke)
- andalso is_valid_map_key_value(Ve);
- (_,_) -> false
- end, true, Ps);
- {record,_,_,Fs} ->
- foldl(fun
- ({record_field,_,Ke,Ve},B) ->
- B andalso is_valid_map_key_value(Ke)
- andalso is_valid_map_key_value(Ve)
- end,true,Fs);
- {bin,_,Es} ->
- % only check for value expressions to be valid
- % invalid binary expressions are later checked in
- % core and kernel
- foldl(fun
- ({bin_element,_,E,_,_},B) ->
- B andalso is_valid_map_key_value(E)
- end,true,Es);
- Val -> is_pattern_expr(Val)
- end.
-
%% record_def(Line, RecordName, [RecField], State) -> State.
%% Add a record definition if it does not already exist. Normalise
%% so that all fields have explicit initial value.
record_def(Line, Name, Fs0, St0) ->
- case dict:is_key(Name, St0#lint.records) of
+ case is_map_key(Name, St0#lint.records) of
true -> add_error(Line, {redefine_record,Name}, St0);
false ->
{Fs1,St1} = def_fields(normalise_fields(Fs0), Name, St0),
- St2 = St1#lint{records=dict:store(Name, {Line,Fs1},
+ St2 = St1#lint{records=maps:put(Name, {Line,Fs1},
St1#lint.records)},
Types = [T || {typed_record_field, _, T} <- Fs0],
check_type({type, nowarn(), product, Types}, St2)
@@ -2627,7 +2691,7 @@ normalise_fields(Fs) ->
%% Check if a record exists. Set State.
exist_record(Line, Name, St) ->
- case dict:is_key(Name, St#lint.records) of
+ case is_map_key(Name, St#lint.records) of
true -> used_record(Name, St);
false -> add_error(Line, {undefined_record,Name}, St)
end.
@@ -2644,13 +2708,13 @@ exist_record(Line, Name, St) ->
%% {UpdatedVarTable,State}
check_record(Line, Name, St, CheckFun) ->
- case dict:find(Name, St#lint.records) of
+ case maps:find(Name, St#lint.records) of
{ok,{_Line,Fields}} -> CheckFun(Fields, used_record(Name, St));
error -> {[],add_error(Line, {undefined_record,Name}, St)}
end.
used_record(Name, #lint{usage=Usage}=St) ->
- UsedRecs = sets:add_element(Name, Usage#usage.used_records),
+ UsedRecs = gb_sets:add_element(Name, Usage#usage.used_records),
St#lint{usage = Usage#usage{used_records=UsedRecs}}.
%%% Record check functions.
@@ -2791,7 +2855,7 @@ type_def(Attr, Line, TypeName, ProtoType, Args, St0) ->
Info = #typeinfo{attr = Attr, line = Line},
StoreType =
fun(St) ->
- NewDefs = dict:store(TypePair, Info, TypeDefs),
+ NewDefs = maps:put(TypePair, Info, TypeDefs),
CheckType = {type, nowarn(), product, [ProtoType|Args]},
check_type(CheckType, St#lint{types=NewDefs})
end,
@@ -2811,7 +2875,7 @@ type_def(Attr, Line, TypeName, ProtoType, Args, St0) ->
end
end;
false ->
- case dict:is_key(TypePair, TypeDefs) of
+ case is_map_key(TypePair, TypeDefs) of
true ->
add_error(Line, {redefine_type, TypePair}, St0);
false ->
@@ -2833,8 +2897,8 @@ is_underspecified({type,_,any,[]}, 0) -> true;
is_underspecified(_ProtType, _Arity) -> false.
check_type(Types, St) ->
- {SeenVars, St1} = check_type(Types, dict:new(), St),
- dict:fold(fun(Var, {seen_once, Line}, AccSt) ->
+ {SeenVars, St1} = check_type(Types, maps:new(), St),
+ maps:fold(fun(Var, {seen_once, Line}, AccSt) ->
case atom_to_list(Var) of
"_"++_ -> AccSt;
_ -> add_error(Line, {singleton_typevar, Var}, AccSt)
@@ -2862,10 +2926,10 @@ check_type({atom, _L, _}, SeenVars, St) -> {SeenVars, St};
check_type({var, _L, '_'}, SeenVars, St) -> {SeenVars, St};
check_type({var, L, Name}, SeenVars, St) ->
NewSeenVars =
- case dict:find(Name, SeenVars) of
- {ok, {seen_once, _}} -> dict:store(Name, seen_multiple, SeenVars);
+ case maps:find(Name, SeenVars) of
+ {ok, {seen_once, _}} -> maps:put(Name, seen_multiple, SeenVars);
{ok, seen_multiple} -> SeenVars;
- error -> dict:store(Name, {seen_once, L}, SeenVars)
+ error -> maps:put(Name, {seen_once, L}, SeenVars)
end,
{NewSeenVars, St};
check_type({type, L, bool, []}, SeenVars, St) ->
@@ -2924,7 +2988,7 @@ check_type({type, La, TypeName, Args}, SeenVars, St) ->
andalso obsolete_builtin_type(TypePair)),
St1 = case Obsolete of
{deprecated, Repl, _} when element(1, Repl) =/= Module ->
- case dict:find(TypePair, Types) of
+ case maps:find(TypePair, Types) of
{ok, _} ->
used_type(TypePair, La, St);
error ->
@@ -2953,7 +3017,7 @@ check_type(I, SeenVars, St) ->
end.
check_record_types(Line, Name, Fields, SeenVars, St) ->
- case dict:find(Name, St#lint.records) of
+ case maps:find(Name, St#lint.records) of
{ok,{_L,DefFields}} ->
case lists:all(fun({type, _, field_type, _}) -> true;
(_) -> false
@@ -2988,7 +3052,7 @@ check_record_types([], _Name, _DefFields, SeenVars, St, _SeenFields) ->
used_type(TypePair, L, #lint{usage = Usage, file = File} = St) ->
OldUsed = Usage#usage.used_types,
- UsedTypes = dict:store(TypePair, erl_anno:set_file(File, L), OldUsed),
+ UsedTypes = maps:put(TypePair, erl_anno:set_file(File, L), OldUsed),
St#lint{usage=Usage#usage{used_types=UsedTypes}}.
is_default_type({Name, NumberOfTypeVariables}) ->
@@ -3012,8 +3076,8 @@ spec_decl(Line, MFA0, TypeSpecs, St00 = #lint{specs = Specs, module = Mod}) ->
{_M, _F, Arity} -> MFA0
end,
St0 = check_module_name(element(1, MFA), Line, St00),
- St1 = St0#lint{specs = dict:store(MFA, Line, Specs)},
- case dict:is_key(MFA, Specs) of
+ St1 = St0#lint{specs = maps:put(MFA, Line, Specs)},
+ case is_map_key(MFA, Specs) of
true -> add_error(Line, {redefine_spec, MFA0}, St1);
false ->
case MFA of
@@ -3034,8 +3098,8 @@ callback_decl(Line, MFA0, TypeSpecs,
add_error(Line, {bad_callback, MFA0}, St1);
{F, Arity} ->
MFA = {Mod, F, Arity},
- St1 = St0#lint{callbacks = dict:store(MFA, Line, Callbacks)},
- case dict:is_key(MFA, Callbacks) of
+ St1 = St0#lint{callbacks = maps:put(MFA, Line, Callbacks)},
+ case is_map_key(MFA, Callbacks) of
true -> add_error(Line, {redefine_callback, MFA0}, St1);
false -> check_specs(TypeSpecs, callback_wrong_arity,
Arity, St1)
@@ -3058,8 +3122,8 @@ optional_cbs(_Line, [], St) ->
optional_cbs(Line, [{F,A}|FAs], St0) ->
#lint{optional_callbacks = OptionalCbs, module = Mod} = St0,
MFA = {Mod, F, A},
- St1 = St0#lint{optional_callbacks = dict:store(MFA, Line, OptionalCbs)},
- St2 = case dict:is_key(MFA, OptionalCbs) of
+ St1 = St0#lint{optional_callbacks = maps:put(MFA, Line, OptionalCbs)},
+ St2 = case is_map_key(MFA, OptionalCbs) of
true ->
add_error(Line, {redefine_optional_callback, {F,A}}, St1);
false ->
@@ -3119,7 +3183,7 @@ check_specs_without_function(#lint{module=Mod,defined=Funcs,specs=Specs}=St) ->
end;
({_M, _F, _A}, _Line, AccSt) -> AccSt
end,
- dict:fold(Fun, St, Specs).
+ maps:fold(Fun, St, Specs).
%% This generates warnings for functions without specs; if the user has
%% specified both options, we do not generate the same warnings twice.
@@ -3137,7 +3201,7 @@ check_functions_without_spec(Forms, St0) ->
end.
add_missing_spec_warnings(Forms, St0, Type) ->
- Specs = [{F,A} || {_M,F,A} <- dict:fetch_keys(St0#lint.specs)],
+ Specs = [{F,A} || {_M,F,A} <- maps:keys(St0#lint.specs)],
Warns = %% functions + line numbers for which we should warn
case Type of
all ->
@@ -3163,7 +3227,7 @@ check_unused_types_1(Forms, #lint{usage=Usage, types=Ts, exp_types=ExpTs}=St) ->
case [File || {attribute,_L,file,{File,_Line}} <- Forms] of
[FirstFile|_] ->
D = Usage#usage.used_types,
- L = gb_sets:to_list(ExpTs) ++ dict:fetch_keys(D),
+ L = gb_sets:to_list(ExpTs) ++ maps:keys(D),
UsedTypes = gb_sets:from_list(L),
FoldFun =
fun({{record, _}=_Type, 0}, _, AccSt) ->
@@ -3182,7 +3246,7 @@ check_unused_types_1(Forms, #lint{usage=Usage, types=Ts, exp_types=ExpTs}=St) ->
AccSt
end
end,
- dict:fold(FoldFun, St, Ts);
+ maps:fold(FoldFun, St, Ts);
[] ->
St
end.
@@ -3200,7 +3264,7 @@ check_local_opaque_types(St) ->
add_warning(FileLine, Warn, AccSt)
end
end,
- dict:fold(FoldFun, St, Ts).
+ maps:fold(FoldFun, St, Ts).
check_dialyzer_attribute(Forms, St0) ->
Vals = [{L,V} ||
@@ -3444,7 +3508,7 @@ handle_generator(P,E,Vt,Uvt,St0) ->
handle_bitstring_gen_pat({bin,_,Segments=[_|_]},St) ->
case lists:last(Segments) of
- {bin_element,Line,{var,_,_},default,Flags} when is_list(Flags) ->
+ {bin_element,Line,_,default,Flags} when is_list(Flags) ->
case member(binary, Flags) orelse member(bytes, Flags)
orelse member(bits, Flags) orelse member(bitstring, Flags) of
true ->
@@ -3590,7 +3654,13 @@ pat_binsize_var(V, Line, Vt, Bvt, St) ->
%% exported vars are probably safe, warn only if warn_export_vars is
%% set.
-expr_var(V, Line, Vt, St) ->
+expr_var(V, Line, Vt, #lint{bvt=none}=St) ->
+ do_expr_var(V, Line, Vt, St);
+expr_var(V, Line, Vt0, #lint{bvt=Bvt0}=St0) when is_list(Bvt0) ->
+ {Vt,Bvt,St} = pat_binsize_var(V, Line, Vt0, Bvt0, St0),
+ {Vt,St#lint{bvt=vtmerge(Bvt0, Bvt)}}.
+
+do_expr_var(V, Line, Vt, St) ->
case orddict:find(V, Vt) of
{ok,{bound,_Usage,Ls}} ->
{[{V,{bound,used,Ls}}],St};
@@ -3846,8 +3916,8 @@ deprecated_type(L, M, N, As, St) ->
false ->
St
end;
- {removed, Replacement, Rel} ->
- add_warning(L, {removed_type, {M,N,NAs}, Replacement, Rel}, St);
+ {removed, String} ->
+ add_warning(L, {removed_type, {M,N,NAs}, String}, St);
no ->
St
end.
@@ -4122,3 +4192,13 @@ no_guard_bif_clash(St,{F,A}) ->
is_imported_from_erlang(St#lint.imports,{F,A})
)
).
+
+%% maps_prepend(Key, Value, Map) -> Map.
+
+maps_prepend(Key, Value, Map) ->
+ case maps:find(Key, Map) of
+ {ok, Values} ->
+ maps:put(Key, [Value|Values], Map);
+ error ->
+ maps:put(Key, [Value], Map)
+ end.
diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl
index 739f786321..eab8da4ab7 100644
--- a/lib/stdlib/src/erl_parse.yrl
+++ b/lib/stdlib/src/erl_parse.yrl
@@ -608,6 +608,13 @@ Erlang code.
-export_type([abstract_clause/0, abstract_expr/0, abstract_form/0,
abstract_type/0, form_info/0, error_info/0]).
+%% The following types are exported because they are used by syntax_tools
+-export_type([af_binelement/1, af_generator/0, af_remote_function/0]).
+
+%% Removed functions
+-removed([{set_line,2,"use erl_anno:set_line/2"},
+ {get_attributes,1,"erl_anno:{column,line,location,text}/1 instead"},
+ {get_attribute,2,"erl_anno:{column,line,location,text}/1 instead"}]).
%% Start of Abstract Format
@@ -637,7 +644,7 @@ Erlang code.
-type af_export() :: {'attribute', anno(), 'export', af_fa_list()}.
--type af_import() :: {'attribute', anno(), 'import', af_fa_list()}.
+-type af_import() :: {'attribute', anno(), 'import', {module(), af_fa_list()}}.
-type af_fa_list() :: [{function_name(), arity()}].
@@ -1455,7 +1462,19 @@ abstract(List, A, E) when is_list(List) ->
abstract(Tuple, A, E) when is_tuple(Tuple) ->
{tuple,A,abstract_tuple_list(tuple_to_list(Tuple), A, E)};
abstract(Map, A, E) when is_map(Map) ->
- {map,A,abstract_map_fields(maps:to_list(Map),A,E)}.
+ {map,A,abstract_map_fields(maps:to_list(Map),A,E)};
+abstract(Fun, A, E) when is_function(Fun) ->
+ case erlang:fun_info(Fun, type) of
+ {type, external} ->
+ Info = erlang:fun_info(Fun),
+ {module, M} = lists:keyfind(module, 1, Info),
+ {name, F} = lists:keyfind(name, 1, Info),
+ {arity, Arity} = lists:keyfind(arity, 1, Info),
+ {'fun', A, {function,
+ abstract(M, A, E),
+ abstract(F, A, E),
+ abstract(Arity, A, E)}}
+ end.
abstract_list([H|T], String, A, E) ->
case is_integer(H) andalso H >= 0 andalso E(H) of
diff --git a/lib/stdlib/src/erl_pp.erl b/lib/stdlib/src/erl_pp.erl
index daa172af50..c706a5c945 100644
--- a/lib/stdlib/src/erl_pp.erl
+++ b/lib/stdlib/src/erl_pp.erl
@@ -31,7 +31,8 @@
-import(erl_parse, [inop_prec/1,preop_prec/1,func_prec/0,max_prec/0,
type_inop_prec/1, type_preop_prec/1]).
--define(MAXLINE, 72).
+-define(DEFAULT_LINEWIDTH, 72).
+-define(DEFAULT_INDENT, 4).
-type(hook_function() :: none
| fun((Expr :: erl_parse:abstract_expr(),
@@ -42,10 +43,13 @@
-type(option() :: {hook, hook_function()}
| {encoding, latin1 | unicode | utf8}
- | {quote_singleton_atom_types, boolean()}).
+ | {quote_singleton_atom_types, boolean()}
+ | {linewidth, pos_integer()}
+ | {indent, pos_integer()}).
-type(options() :: hook_function() | [option()]).
--record(pp, {value_fun, singleton_atom_type_fun, string_fun, char_fun}).
+-record(pp, {value_fun, singleton_atom_type_fun, string_fun, char_fun,
+ linewidth=?DEFAULT_LINEWIDTH, indent=?DEFAULT_INDENT}).
-record(options, {hook, encoding, opts}).
@@ -208,10 +212,14 @@ options(Hook) ->
state(Options) when is_list(Options) ->
Quote = proplists:get_bool(quote_singleton_atom_types, Options),
- case encoding(Options) of
- latin1 -> latin1_state(Quote);
- unicode -> unicode_state(Quote)
- end;
+ State =
+ case encoding(Options) of
+ latin1 -> latin1_state(Quote);
+ unicode -> unicode_state(Quote)
+ end,
+ Indent = proplists:get_value(indent, Options, ?DEFAULT_INDENT),
+ LineWidth = proplists:get_value(linewidth, Options, ?DEFAULT_LINEWIDTH),
+ State#pp{indent=Indent, linewidth=LineWidth};
state(_Hook) ->
latin1_state(false).
@@ -1020,7 +1028,7 @@ f({seq,Before,After,Sep,LItems}, I0, ST, WT, PP) ->
true ->
0
end,
- case same_line(I0, Sizes, NSepChars) of
+ case same_line(I0, Sizes, NSepChars, PP) of
{yes,Size} ->
Chars = if
NSepChars > 0 -> insert_sep(CharsL, $\s);
@@ -1028,9 +1036,9 @@ f({seq,Before,After,Sep,LItems}, I0, ST, WT, PP) ->
end,
{BCharsL++Chars,Size};
no ->
- CharsList = handle_step(CharsSizeL, I, ST),
+ CharsList = handle_step(CharsSizeL, I, ST, PP),
{LChars, LSize} =
- maybe_newlines(CharsList, LItems, I, NSepChars, ST),
+ maybe_newlines(CharsList, LItems, I, NSepChars, ST, PP),
{[BCharsL,LChars],nsz(LSize, I0)}
end;
f({force_nl,_ExtraInfoItem,Item}, I, ST, WT, PP) when I < 0 ->
@@ -1047,7 +1055,7 @@ f({prefer_nl,Sep,LItems}, I0, ST, WT, PP) ->
Sizes =:= [] ->
{[], 0};
true ->
- {insert_newlines(CharsSize2L, I0, ST),
+ {insert_newlines(CharsSize2L, I0, ST, PP),
nsz(lists:last(Sizes), I0)}
end;
f({value,V}, I, ST, WT, PP) ->
@@ -1071,8 +1079,6 @@ f({ehook,HookExpr,Precedence,{Mod,Func,Eas}=ModFuncEas}, I, _ST, _WT, _PP) ->
f(WordName, _I, _ST, WT, _PP) when is_atom(WordName) ->
word(WordName, WT).
--define(IND, 4).
-
%% fl(ListItems, I0, ST, WT) -> [[CharsSize1,CharsSize2]]
%% ListItems = [{Item,Items}|Item]
fl([], _Sep, I0, After, ST, WT, PP) ->
@@ -1080,15 +1086,15 @@ fl([], _Sep, I0, After, ST, WT, PP) ->
fl(CItems, Sep0, I0, After, ST, WT, PP) ->
F = fun({step,Item1,Item2}, S) ->
[f(Item1, I0, ST, WT, PP),
- f([Item2,S], incr(I0, ?IND), ST, WT, PP)];
+ f([Item2,S], incr(I0, PP#pp.indent), ST, WT, PP)];
({cstep,Item1,Item2}, S) ->
{_,Sz1} = CharSize1 = f(Item1, I0, ST, WT, PP),
if
- is_integer(Sz1), Sz1 < ?IND ->
+ is_integer(Sz1), Sz1 < PP#pp.indent ->
Item2p = [leaf("\s"),Item2,S],
[consecutive(Item2p, CharSize1, I0, ST, WT, PP),{[],0}];
true ->
- [CharSize1,f([Item2,S], incr(I0, ?IND), ST, WT, PP)]
+ [CharSize1,f([Item2,S], incr(I0, PP#pp.indent), ST, WT, PP)]
end;
({reserved,Word}, S) ->
[f([Word,S], I0, ST, WT, PP),{[],0}];
@@ -1127,58 +1133,58 @@ unz1(CharSizes) ->
nonzero(CharSizes) ->
lists:filter(fun({_,Sz}) -> Sz =/= 0 end, CharSizes).
-maybe_newlines([{Chars,Size}], [], _I, _NSepChars, _ST) ->
+maybe_newlines([{Chars,Size}], [], _I, _NSepChars, _ST, _PP) ->
{Chars,Size};
-maybe_newlines(CharsSizeList, Items, I, NSepChars, ST) when I >= 0 ->
- maybe_sep(CharsSizeList, Items, I, NSepChars, nl_indent(I, ST)).
+maybe_newlines(CharsSizeList, Items, I, NSepChars, ST, PP) when I >= 0 ->
+ maybe_sep(CharsSizeList, Items, I, NSepChars, nl_indent(I, ST), PP).
-maybe_sep([{Chars1,Size1}|CharsSizeL], [Item|Items], I0, NSepChars, Sep) ->
+maybe_sep([{Chars1,Size1}|CharsSizeL], [Item|Items], I0, NSepChars, Sep, PP) ->
I1 = case classify_item(Item) of
atomic ->
I0 + Size1;
_ ->
- ?MAXLINE+1
+ PP#pp.linewidth+1
end,
- maybe_sep1(CharsSizeL, Items, I0, I1, Sep, NSepChars, Size1, [Chars1]).
+ maybe_sep1(CharsSizeL, Items, I0, I1, Sep, NSepChars, Size1, [Chars1], PP).
maybe_sep1([{Chars,Size}|CharsSizeL], [Item|Items],
- I0, I, Sep, NSepChars, Sz0, A) ->
+ I0, I, Sep, NSepChars, Sz0, A, PP) ->
case classify_item(Item) of
atomic when is_integer(Size) ->
Size1 = Size + 1,
I1 = I + Size1,
if
- I1 =< ?MAXLINE ->
+ I1 =< PP#pp.linewidth ->
A1 = if
NSepChars > 0 -> [Chars,$\s|A];
true -> [Chars|A]
end,
maybe_sep1(CharsSizeL, Items, I0, I1, Sep, NSepChars,
- Sz0 + Size1, A1);
+ Sz0 + Size1, A1, PP);
true ->
A1 = [Chars,Sep|A],
maybe_sep1(CharsSizeL, Items, I0, I0 + Size, Sep,
- NSepChars, Size1, A1)
+ NSepChars, Size1, A1, PP)
end;
_ ->
A1 = [Chars,Sep|A],
- maybe_sep1(CharsSizeL, Items, I0, ?MAXLINE+1, Sep, NSepChars,
- 0, A1)
+ maybe_sep1(CharsSizeL, Items, I0, PP#pp.linewidth+1, Sep, NSepChars,
+ 0, A1, PP)
end;
-maybe_sep1(_CharsSizeL, _Items, _Io, _I, _Sep, _NSepChars, Sz, A) ->
+maybe_sep1(_CharsSizeL, _Items, _Io, _I, _Sep, _NSepChars, Sz, A, _PP) ->
{lists:reverse(A), Sz}.
-insert_newlines(CharsSizesL, I, ST) when I >= 0 ->
- {CharsL, _} = unz1(handle_step(CharsSizesL, I, ST)),
+insert_newlines(CharsSizesL, I, ST, PP) when I >= 0 ->
+ {CharsL, _} = unz1(handle_step(CharsSizesL, I, ST, PP)),
insert_nl(CharsL, I, ST).
-handle_step(CharsSizesL, I, ST) ->
+handle_step(CharsSizesL, I, ST, PP) ->
map(fun([{_C1,0},{_C2,0}]) ->
{[], 0};
([{C1,Sz1},{_C2,0}]) ->
{C1, Sz1};
([{C1,Sz1},{C2,Sz2}]) when Sz2 > 0 ->
- {insert_nl([C1,C2], I+?IND, ST),line_size([Sz1,Sz2])}
+ {insert_nl([C1,C2], I+PP#pp.indent, ST),line_size([Sz1,Sz2])}
end, CharsSizesL).
insert_nl(CharsL, I, ST) ->
@@ -1198,10 +1204,10 @@ classify_item(Atom) when is_atom(Atom) -> atomic;
classify_item({leaf, _, _}) -> atomic;
classify_item(_) -> complex.
-same_line(I0, SizeL, NSepChars) ->
+same_line(I0, SizeL, NSepChars, PP) ->
try
Size = lists:sum(SizeL) + NSepChars,
- true = incr(I0, Size) =< ?MAXLINE,
+ true = incr(I0, Size) =< PP#pp.linewidth,
{yes,Size}
catch _:_ ->
no
@@ -1269,7 +1275,7 @@ write_a_char(C, PP) ->
write_a_string(S, I, PP) when I < 0; S =:= [] ->
flat_leaf(write_string(S, PP));
write_a_string(S, I, PP) ->
- Len = erlang:max(?MAXLINE-I, ?MIN_SUBSTRING),
+ Len = erlang:max(PP#pp.linewidth-I, ?MIN_SUBSTRING),
{list,write_a_string(S, Len, Len, PP)}.
write_a_string([], _N, _Len, _PP) ->
diff --git a/lib/stdlib/src/erl_scan.erl b/lib/stdlib/src/erl_scan.erl
index 4774c4bf19..0854e15177 100644
--- a/lib/stdlib/src/erl_scan.erl
+++ b/lib/stdlib/src/erl_scan.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2017. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2019. 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.
@@ -66,6 +66,17 @@
token/0,
tokens_result/0]).
+%% Removed functions and types
+-removed([{set_attribute,3,"use erl_anno:set_line/2 instead"},
+ {attributes_info,'_',
+ "erl_anno:{column,line,location,text}/1 instead"},
+ {token_info,'_',
+ "erl_scan:{category,column,line,location,symbol,text}/1 instead"}]).
+
+-removed_type([{column,0,"use erl_anno:column() instead"},
+ {line,0,"use erl_anno:line() instead"},
+ {location,0,"use erl_anno:location() instead"}]).
+
%%%
%%% Defines and type definitions
%%%
@@ -249,7 +260,7 @@ string_thing(_) -> "string".
-define(WHITE_SPACE(C),
is_integer(C) andalso
(C >= $\000 andalso C =< $\s orelse C >= $\200 andalso C =< $\240)).
--define(DIGIT(C), C >= $0, C =< $9).
+-define(DIGIT(C), C >= $0 andalso C =< $9).
-define(CHAR(C), is_integer(C), C >= 0).
-define(UNICODE(C),
is_integer(C) andalso
@@ -379,7 +390,7 @@ scan1([$\%|Cs], St, Line, Col, Toks) when not St#erl_scan.comment ->
scan1([$\%=C|Cs], St, Line, Col, Toks) ->
scan_comment(Cs, St, Line, Col, Toks, [C]);
scan1([C|Cs], St, Line, Col, Toks) when ?DIGIT(C) ->
- scan_number(Cs, St, Line, Col, Toks, [C]);
+ scan_number(Cs, St, Line, Col, Toks, [C], no_underscore);
scan1("..."++Cs, St, Line, Col, Toks) ->
tok2(Cs, St, Line, Col, Toks, "...", '...', 3);
scan1(".."=Cs, _St, Line, Col, Toks) ->
@@ -938,27 +949,35 @@ escape_char($s) -> $\s; % \s = SPC
escape_char($d) -> $\d; % \d = DEL
escape_char(C) -> C.
-scan_number([C|Cs], St, Line, Col, Toks, Ncs) when ?DIGIT(C) ->
- scan_number(Cs, St, Line, Col, Toks, [C|Ncs]);
-scan_number([$.,C|Cs], St, Line, Col, Toks, Ncs) when ?DIGIT(C) ->
- scan_fraction(Cs, St, Line, Col, Toks, [C,$.|Ncs]);
-scan_number([$.]=Cs, _St, Line, Col, Toks, Ncs) ->
- {more,{Cs,Col,Toks,Line,Ncs,fun scan_number/6}};
-scan_number([$#|Cs]=Cs0, St, Line, Col, Toks, Ncs0) ->
+scan_number(Cs, St, Line, Col, Toks, {Ncs, Us}) ->
+ scan_number(Cs, St, Line, Col, Toks, Ncs, Us).
+
+scan_number([C|Cs], St, Line, Col, Toks, Ncs, Us) when ?DIGIT(C) ->
+ scan_number(Cs, St, Line, Col, Toks, [C|Ncs], Us);
+scan_number([$_,Next|Cs], St, Line, Col, Toks, [Prev|_]=Ncs, _Us) when
+ ?DIGIT(Next) andalso ?DIGIT(Prev) ->
+ scan_number(Cs, St, Line, Col, Toks, [Next,$_|Ncs], with_underscore);
+scan_number([$_]=Cs, _St, Line, Col, Toks, Ncs, Us) ->
+ {more,{Cs,Col,Toks,Line,{Ncs,Us},fun scan_number/6}};
+scan_number([$.,C|Cs], St, Line, Col, Toks, Ncs, Us) when ?DIGIT(C) ->
+ scan_fraction(Cs, St, Line, Col, Toks, [C,$.|Ncs], Us);
+scan_number([$.]=Cs, _St, Line, Col, Toks, Ncs, Us) ->
+ {more,{Cs,Col,Toks,Line,{Ncs,Us},fun scan_number/6}};
+scan_number([$#|Cs]=Cs0, St, Line, Col, Toks, Ncs0, Us) ->
Ncs = lists:reverse(Ncs0),
- case catch list_to_integer(Ncs) of
+ case catch list_to_integer(remove_digit_separators(Ncs, Us)) of
B when B >= 2, B =< 1+$Z-$A+10 ->
Bcs = Ncs++[$#],
- scan_based_int(Cs, St, Line, Col, Toks, {B,[],Bcs});
+ scan_based_int(Cs, St, Line, Col, Toks, B, [], Bcs, no_underscore);
B ->
Len = length(Ncs),
scan_error({base,B}, Line, Col, Line, incr_column(Col, Len), Cs0)
end;
-scan_number([]=Cs, _St, Line, Col, Toks, Ncs) ->
- {more,{Cs,Col,Toks,Line,Ncs,fun scan_number/6}};
-scan_number(Cs, St, Line, Col, Toks, Ncs0) ->
+scan_number([]=Cs, _St, Line, Col, Toks, Ncs, Us) ->
+ {more,{Cs,Col,Toks,Line,{Ncs,Us},fun scan_number/6}};
+scan_number(Cs, St, Line, Col, Toks, Ncs0, Us) ->
Ncs = lists:reverse(Ncs0),
- case catch list_to_integer(Ncs) of
+ case catch list_to_integer(remove_digit_separators(Ncs, Us)) of
N when is_integer(N) ->
tok3(Cs, St, Line, Col, Toks, integer, Ncs, N);
_ ->
@@ -966,20 +985,33 @@ scan_number(Cs, St, Line, Col, Toks, Ncs0) ->
scan_error({illegal,integer}, Line, Col, Line, Ncol, Cs)
end.
-scan_based_int([C|Cs], St, Line, Col, Toks, {B,Ncs,Bcs})
- when ?DIGIT(C), C < $0+B ->
- scan_based_int(Cs, St, Line, Col, Toks, {B,[C|Ncs],Bcs});
-scan_based_int([C|Cs], St, Line, Col, Toks, {B,Ncs,Bcs})
- when C >= $A, B > 10, C < $A+B-10 ->
- scan_based_int(Cs, St, Line, Col, Toks, {B,[C|Ncs],Bcs});
-scan_based_int([C|Cs], St, Line, Col, Toks, {B,Ncs,Bcs})
- when C >= $a, B > 10, C < $a+B-10 ->
- scan_based_int(Cs, St, Line, Col, Toks, {B,[C|Ncs],Bcs});
-scan_based_int([]=Cs, _St, Line, Col, Toks, State) ->
- {more,{Cs,Col,Toks,Line,State,fun scan_based_int/6}};
-scan_based_int(Cs, St, Line, Col, Toks, {B,Ncs0,Bcs}) ->
+remove_digit_separators(Number, no_underscore) ->
+ Number;
+remove_digit_separators(Number, with_underscore) ->
+ [C || C <- Number, C =/= $_].
+
+-define(BASED_DIGIT(C, B),
+ ((?DIGIT(C) andalso C < $0 + B)
+ orelse (C >= $A andalso B > 10 andalso C < $A + B - 10)
+ orelse (C >= $a andalso B > 10 andalso C < $a + B - 10))).
+
+scan_based_int(Cs, St, Line, Col, Toks, {B,NCs,BCs,Us}) ->
+ scan_based_int(Cs, St, Line, Col, Toks, B, NCs, BCs, Us).
+
+scan_based_int([C|Cs], St, Line, Col, Toks, B, Ncs, Bcs, Us) when
+ ?BASED_DIGIT(C, B) ->
+ scan_based_int(Cs, St, Line, Col, Toks, B, [C|Ncs], Bcs, Us);
+scan_based_int([$_,Next|Cs], St, Line, Col, Toks, B, [Prev|_]=Ncs, Bcs, _Us)
+ when ?BASED_DIGIT(Next, B) andalso ?BASED_DIGIT(Prev, B) ->
+ scan_based_int(Cs, St, Line, Col, Toks, B, [Next,$_|Ncs], Bcs,
+ with_underscore);
+scan_based_int([$_]=Cs, _St, Line, Col, Toks, B, NCs, BCs, Us) ->
+ {more,{Cs,Col,Toks,Line,{B,NCs,BCs,Us},fun scan_based_int/6}};
+scan_based_int([]=Cs, _St, Line, Col, Toks, B, NCs, BCs, Us) ->
+ {more,{Cs,Col,Toks,Line,{B,NCs,BCs,Us},fun scan_based_int/6}};
+scan_based_int(Cs, St, Line, Col, Toks, B, Ncs0, Bcs, Us) ->
Ncs = lists:reverse(Ncs0),
- case catch erlang:list_to_integer(Ncs, B) of
+ case catch erlang:list_to_integer(remove_digit_separators(Ncs, Us), B) of
N when is_integer(N) ->
tok3(Cs, St, Line, Col, Toks, integer, Bcs++Ncs, N);
_ ->
@@ -988,32 +1020,52 @@ scan_based_int(Cs, St, Line, Col, Toks, {B,Ncs0,Bcs}) ->
scan_error({illegal,integer}, Line, Col, Line, Ncol, Cs)
end.
-scan_fraction([C|Cs], St, Line, Col, Toks, Ncs) when ?DIGIT(C) ->
- scan_fraction(Cs, St, Line, Col, Toks, [C|Ncs]);
-scan_fraction([E|Cs], St, Line, Col, Toks, Ncs) when E =:= $e; E =:= $E ->
- scan_exponent_sign(Cs, St, Line, Col, Toks, [E|Ncs]);
-scan_fraction([]=Cs, _St, Line, Col, Toks, Ncs) ->
- {more,{Cs,Col,Toks,Line,Ncs,fun scan_fraction/6}};
-scan_fraction(Cs, St, Line, Col, Toks, Ncs) ->
- float_end(Cs, St, Line, Col, Toks, Ncs).
-
-scan_exponent_sign([C|Cs], St, Line, Col, Toks, Ncs) when C =:= $+; C =:= $- ->
- scan_exponent(Cs, St, Line, Col, Toks, [C|Ncs]);
-scan_exponent_sign([]=Cs, _St, Line, Col, Toks, Ncs) ->
- {more,{Cs,Col,Toks,Line,Ncs,fun scan_exponent_sign/6}};
-scan_exponent_sign(Cs, St, Line, Col, Toks, Ncs) ->
- scan_exponent(Cs, St, Line, Col, Toks, Ncs).
-
-scan_exponent([C|Cs], St, Line, Col, Toks, Ncs) when ?DIGIT(C) ->
- scan_exponent(Cs, St, Line, Col, Toks, [C|Ncs]);
-scan_exponent([]=Cs, _St, Line, Col, Toks, Ncs) ->
- {more,{Cs,Col,Toks,Line,Ncs,fun scan_exponent/6}};
-scan_exponent(Cs, St, Line, Col, Toks, Ncs) ->
- float_end(Cs, St, Line, Col, Toks, Ncs).
-
-float_end(Cs, St, Line, Col, Toks, Ncs0) ->
+scan_fraction(Cs, St, Line, Col, Toks, {Ncs,Us}) ->
+ scan_fraction(Cs, St, Line, Col, Toks, Ncs, Us).
+
+scan_fraction([C|Cs], St, Line, Col, Toks, Ncs, Us) when ?DIGIT(C) ->
+ scan_fraction(Cs, St, Line, Col, Toks, [C|Ncs], Us);
+scan_fraction([$_,Next|Cs], St, Line, Col, Toks, [Prev|_]=Ncs, _Us) when
+ ?DIGIT(Next) andalso ?DIGIT(Prev) ->
+ scan_fraction(Cs, St, Line, Col, Toks, [Next,$_|Ncs], with_underscore);
+scan_fraction([$_]=Cs, _St, Line, Col, Toks, Ncs, Us) ->
+ {more,{Cs,Col,Toks,Line,{Ncs,Us},fun scan_fraction/6}};
+scan_fraction([E|Cs], St, Line, Col, Toks, Ncs, Us) when E =:= $e; E =:= $E ->
+ scan_exponent_sign(Cs, St, Line, Col, Toks, [E|Ncs], Us);
+scan_fraction([]=Cs, _St, Line, Col, Toks, Ncs, Us) ->
+ {more,{Cs,Col,Toks,Line,{Ncs,Us},fun scan_fraction/6}};
+scan_fraction(Cs, St, Line, Col, Toks, Ncs, Us) ->
+ float_end(Cs, St, Line, Col, Toks, Ncs, Us).
+
+scan_exponent_sign(Cs, St, Line, Col, Toks, {Ncs, Us}) ->
+ scan_exponent_sign(Cs, St, Line, Col, Toks, Ncs, Us).
+
+scan_exponent_sign([C|Cs], St, Line, Col, Toks, Ncs, Us) when
+ C =:= $+; C =:= $- ->
+ scan_exponent(Cs, St, Line, Col, Toks, [C|Ncs], Us);
+scan_exponent_sign([]=Cs, _St, Line, Col, Toks, Ncs, Us) ->
+ {more,{Cs,Col,Toks,Line,{Ncs,Us},fun scan_exponent_sign/6}};
+scan_exponent_sign(Cs, St, Line, Col, Toks, Ncs, Us) ->
+ scan_exponent(Cs, St, Line, Col, Toks, Ncs, Us).
+
+scan_exponent(Cs, St, Line, Col, Toks, {Ncs, Us}) ->
+ scan_exponent(Cs, St, Line, Col, Toks, Ncs, Us).
+
+scan_exponent([C|Cs], St, Line, Col, Toks, Ncs, Us) when ?DIGIT(C) ->
+ scan_exponent(Cs, St, Line, Col, Toks, [C|Ncs], Us);
+scan_exponent([$_,Next|Cs], St, Line, Col, Toks, [Prev|_]=Ncs, _) when
+ ?DIGIT(Next) andalso ?DIGIT(Prev) ->
+ scan_exponent(Cs, St, Line, Col, Toks, [Next,$_|Ncs], with_underscore);
+scan_exponent([$_]=Cs, _St, Line, Col, Toks, Ncs, Us) ->
+ {more,{Cs,Col,Toks,Line,{Ncs,Us},fun scan_exponent/6}};
+scan_exponent([]=Cs, _St, Line, Col, Toks, Ncs, Us) ->
+ {more,{Cs,Col,Toks,Line,{Ncs,Us},fun scan_exponent/6}};
+scan_exponent(Cs, St, Line, Col, Toks, Ncs, Us) ->
+ float_end(Cs, St, Line, Col, Toks, Ncs, Us).
+
+float_end(Cs, St, Line, Col, Toks, Ncs0, Us) ->
Ncs = lists:reverse(Ncs0),
- case catch list_to_float(Ncs) of
+ case catch list_to_float(remove_digit_separators(Ncs, Us)) of
F when is_float(F) ->
tok3(Cs, St, Line, Col, Toks, float, Ncs, F);
_ ->
diff --git a/lib/stdlib/src/erl_tar.erl b/lib/stdlib/src/erl_tar.erl
index 78cdd02307..cbfed30b13 100644
--- a/lib/stdlib/src/erl_tar.erl
+++ b/lib/stdlib/src/erl_tar.erl
@@ -321,22 +321,29 @@ do_open(Name, Mode) when is_list(Mode) ->
{error, {Name, Reason}}
end.
-open1({binary,Bin}, read, _Raw, Opts) when is_binary(Bin) ->
+open1({binary,Bin}=Handle, read, _Raw, Opts) when is_binary(Bin) ->
case file:open(Bin, [ram,binary,read]) of
{ok,File} ->
_ = [ram_file:uncompress(File) || lists:member(compressed, Opts)],
{ok, #reader{handle=File,access=read,func=fun file_op/2}};
- Error ->
- Error
+ {error, Reason} ->
+ {error, {Handle, Reason}}
end;
-open1({file, Fd}, read, _Raw, _Opts) ->
- Reader = #reader{handle=Fd,access=read,func=fun file_op/2},
- case do_position(Reader, {cur, 0}) of
- {ok, Pos, Reader2} ->
- {ok, Reader2#reader{pos=Pos}};
- {error, _} = Err ->
- Err
+open1({file, Fd}=Handle, read, [raw], Opts) ->
+ case not lists:member(compressed, Opts) of
+ true ->
+ Reader = #reader{handle=Fd,access=read,func=fun file_op/2},
+ case do_position(Reader, {cur, 0}) of
+ {ok, Pos, Reader2} ->
+ {ok, Reader2#reader{pos=Pos}};
+ {error, Reason} ->
+ {error, {Handle, Reason}}
+ end;
+ false ->
+ {error, {Handle, {incompatible_option, compressed}}}
end;
+open1({file, _Fd}=Handle, read, [], _Opts) ->
+ {error, {Handle, {incompatible_option, cooked}}};
open1(Name, Access, Raw, Opts) when is_list(Name) or is_binary(Name) ->
case file:open(Name, Raw ++ [binary, Access|Opts]) of
{ok, File} ->
@@ -1637,60 +1644,18 @@ write_extracted_element(#tar_header{name=Name0}=Header, Bin, Opts) ->
make_safe_path([$/|Path], Opts) ->
make_safe_path(Path, Opts);
-make_safe_path(Path, #read_opts{cwd=Cwd}) ->
- case filename:safe_relative_path(Path) of
- unsafe ->
- throw({error,{Path,unsafe_path}});
- SafePath ->
- filename:absname(SafePath, Cwd)
+make_safe_path(Path0, #read_opts{cwd=Cwd}) ->
+ case filelib:safe_relative_path(Path0, Cwd) of
+ unsafe -> throw({error,{Path0,unsafe_path}});
+ Path -> filename:absname(Path, Cwd)
end.
-safe_link_name(#tar_header{linkname=Path}, #read_opts{cwd=Cwd}) ->
- case safe_relative_path_links(Path, Cwd) of
- unsafe ->
- throw({error,{Path,unsafe_symlink}});
- SafePath ->
- SafePath
+safe_link_name(#tar_header{linkname=Path0},#read_opts{cwd=Cwd} ) ->
+ case filelib:safe_relative_path(Path0, Cwd) of
+ unsafe -> throw({error,{Path0,unsafe_symlink}});
+ Path -> Path
end.
-safe_relative_path_links(Path, Cwd) ->
- case filename:pathtype(Path) of
- relative -> safe_relative_path_links(filename:split(Path), Cwd, [], "");
- _ -> unsafe
- end.
-
-safe_relative_path_links([Segment|Segments], Cwd, PrevSegments, Acc) ->
- AccSegment = join(Acc, Segment),
- case lists:member(AccSegment, PrevSegments) of
- true ->
- unsafe;
- false ->
- case file:read_link(join(Cwd, AccSegment)) of
- {ok, LinkPath} ->
- case filename:pathtype(LinkPath) of
- relative ->
- safe_relative_path_links(filename:split(LinkPath) ++ Segments,
- Cwd, [AccSegment|PrevSegments], Acc);
- _ ->
- unsafe
- end;
-
- {error, _} ->
- case filename:safe_relative_path(join(Acc, Segment)) of
- unsafe ->
- unsafe;
- NewAcc ->
- safe_relative_path_links(Segments, Cwd,
- [AccSegment|PrevSegments], NewAcc)
- end
- end
- end;
-safe_relative_path_links([], _Cwd, _PrevSegments, Acc) ->
- Acc.
-
-join([], Path) -> Path;
-join(Left, Right) -> filename:join(Left, Right).
-
create_regular(Name, NameInArchive, Bin, Opts) ->
case write_extracted_file(Name, Bin, Opts) of
not_written ->
diff --git a/lib/stdlib/src/escript.erl b/lib/stdlib/src/escript.erl
index 4e9ba1cc16..0e120174fe 100644
--- a/lib/stdlib/src/escript.erl
+++ b/lib/stdlib/src/escript.erl
@@ -780,7 +780,7 @@ interpret(Forms, HasRecs, File, Args) ->
false -> Forms;
true -> erl_expand_records:module(Forms, [])
end,
- Dict = parse_to_dict(Forms2),
+ Dict = parse_to_map(Forms2),
ArgsA = erl_parse:abstract(Args, 0),
Anno = a0(),
Call = {call,Anno,{atom,Anno,main},[ArgsA]},
@@ -824,29 +824,29 @@ format_message(F, [{Mod,E}|Es]) ->
[M|format_message(F, Es)];
format_message(_, []) -> [].
-parse_to_dict(L) -> parse_to_dict(L, dict:new()).
-
-parse_to_dict([{function,_,Name,Arity,Clauses}|T], Dict0) ->
- Dict = dict:store({local, Name,Arity}, Clauses, Dict0),
- parse_to_dict(T, Dict);
-parse_to_dict([{attribute,_,import,{Mod,Funcs}}|T], Dict0) ->
- Dict = lists:foldl(fun(I, D) ->
- dict:store({remote,I}, Mod, D)
- end, Dict0, Funcs),
- parse_to_dict(T, Dict);
-parse_to_dict([_|T], Dict) ->
- parse_to_dict(T, Dict);
-parse_to_dict([], Dict) ->
- Dict.
+parse_to_map(L) -> parse_to_map(L, maps:new()).
+
+parse_to_map([{function,_,Name,Arity,Clauses}|T], Map0) ->
+ Map = maps:put({local, Name,Arity}, Clauses, Map0),
+ parse_to_map(T, Map);
+parse_to_map([{attribute,_,import,{Mod,Funcs}}|T], Map0) ->
+ Map = lists:foldl(fun(I, D) ->
+ maps:put({remote,I}, Mod, D)
+ end, Map0, Funcs),
+ parse_to_map(T, Map);
+parse_to_map([_|T], Map) ->
+ parse_to_map(T, Map);
+parse_to_map([], Map) ->
+ Map.
code_handler(local, [file], _, File) ->
File;
-code_handler(Name, Args, Dict, File) ->
+code_handler(Name, Args, Map, File) ->
%%io:format("code handler=~p~n",[{Name, Args}]),
Arity = length(Args),
- case dict:find({local,Name,Arity}, Dict) of
+ case maps:find({local,Name,Arity}, Map) of
{ok, Cs} ->
- LF = {value,fun(I, J) -> code_handler(I, J, Dict, File) end},
+ LF = {value,fun(I, J) -> code_handler(I, J, Map, File) end},
case erl_eval:match_clause(Cs, Args,erl_eval:new_bindings(),LF) of
{Body, Bs} ->
eval_exprs(Body, Bs, LF, none, none);
@@ -854,7 +854,7 @@ code_handler(Name, Args, Dict, File) ->
erlang:error({function_clause,[{local,Name,Args}]})
end;
error ->
- case dict:find({remote,{Name,Arity}}, Dict) of
+ case maps:find({remote,{Name,Arity}}, Map) of
{ok, Mod} ->
%% io:format("Calling:~p~n",[{Mod,Name,Args}]),
apply(Mod, Name, Args);
diff --git a/lib/stdlib/src/ets.erl b/lib/stdlib/src/ets.erl
index e926e4fcaf..c8f8c9721f 100644
--- a/lib/stdlib/src/ets.erl
+++ b/lib/stdlib/src/ets.erl
@@ -155,6 +155,7 @@ give_away(_, _, _) ->
Tab :: tab(),
InfoList :: [InfoTuple],
InfoTuple :: {compressed, boolean()}
+ | {decentralized_counters, boolean()}
| {heir, pid() | none}
| {id, tid()}
| {keypos, pos_integer()}
@@ -174,7 +175,7 @@ info(_) ->
-spec info(Tab, Item) -> Value | undefined when
Tab :: tab(),
- Item :: binary | compressed | fixed | heir | id | keypos | memory
+ Item :: binary | compressed | decentralized_counters | fixed | heir | id | keypos | memory
| name | named_table | node | owner | protection
| safe_fixed | safe_fixed_monotonic_time | size | stats | type
| write_concurrency | read_concurrency,
@@ -311,6 +312,7 @@ member(_, _) ->
Access :: access(),
Tweaks :: {write_concurrency, boolean()}
| {read_concurrency, boolean()}
+ | {decentralized_counters, boolean()}
| compressed,
Pos :: pos_integer(),
HeirData :: term().
diff --git a/lib/stdlib/src/eval_bits.erl b/lib/stdlib/src/eval_bits.erl
index bb86a65c72..15abb6166b 100644
--- a/lib/stdlib/src/eval_bits.erl
+++ b/lib/stdlib/src/eval_bits.erl
@@ -187,7 +187,6 @@ bin_gen_field({bin_element,Line,{string,SLine,S},Size0,Options0},
Bin0, Bs0, BBs0, Mfun, Efun) ->
{Size1, [Type,{unit,Unit},Sign,Endian]} =
make_bit_type(Line, Size0, Options0),
- match_check_size(Mfun, Size1, BBs0),
{value, Size, _BBs} = Efun(Size1, BBs0),
F = fun(C, Bin, Bs, BBs) ->
bin_gen_field1(Bin, Type, Size, Unit, Sign, Endian,
@@ -200,7 +199,6 @@ bin_gen_field({bin_element,Line,VE,Size0,Options0},
make_bit_type(Line, Size0, Options0),
V = erl_eval:partial_eval(VE),
NewV = coerce_to_float(V, Type),
- match_check_size(Mfun, Size1, BBs0, false),
{value, Size, _BBs} = Efun(Size1, BBs0),
bin_gen_field1(Bin, Type, Size, Unit, Sign, Endian, NewV, Bs0, BBs0, Mfun).
@@ -269,7 +267,6 @@ match_field_1({bin_element,Line,{string,SLine,S},Size0,Options0},
{Size1, [Type,{unit,Unit},Sign,Endian]} =
make_bit_type(Line, Size0, Options0),
Size2 = erl_eval:partial_eval(Size1),
- match_check_size(Mfun, Size2, BBs0),
{value, Size, _BBs} = Efun(Size2, BBs0),
F = fun(C, Bin, Bs, BBs) ->
match_field(Bin, Type, Size, Unit, Sign, Endian,
@@ -283,7 +280,6 @@ match_field_1({bin_element,Line,VE,Size0,Options0},
V = erl_eval:partial_eval(VE),
NewV = coerce_to_float(V, Type),
Size2 = erl_eval:partial_eval(Size1),
- match_check_size(Mfun, Size2, BBs0),
{value, Size, _BBs} = Efun(Size2, BBs0),
match_field(Bin, Type, Size, Unit, Sign, Endian, NewV, Bs0, BBs0, Mfun).
@@ -387,24 +383,3 @@ make_bit_type(_Line, Size, Type0) -> %Size evaluates to an integer or 'all'
{ok,Size,Bt} -> {Size,erl_bits:as_list(Bt)};
{error,Reason} -> erlang:raise(error, Reason, ?STACKTRACE)
end.
-
-match_check_size(Mfun, Size, Bs) ->
- match_check_size(Mfun, Size, Bs, true).
-
-match_check_size(Mfun, {var,_,V}, Bs, _AllowAll) ->
- case Mfun(binding, {V,Bs}) of
- {value,_} -> ok;
- unbound -> throw(invalid) % or, rather, error({unbound,V})
- end;
-match_check_size(_, {atom,_,all}, _Bs, true) ->
- ok;
-match_check_size(_, {atom,_,all}, _Bs, false) ->
- throw(invalid);
-match_check_size(_, {atom,_,undefined}, _Bs, _AllowAll) ->
- ok;
-match_check_size(_, {integer,_,_}, _Bs, _AllowAll) ->
- ok;
-match_check_size(_, {value,_,_}, _Bs, _AllowAll) ->
- ok; %From the debugger.
-match_check_size(_, _, _Bs, _AllowAll) ->
- throw(invalid).
diff --git a/lib/stdlib/src/filelib.erl b/lib/stdlib/src/filelib.erl
index d1a5a4dc35..b4c9ffc1b9 100644
--- a/lib/stdlib/src/filelib.erl
+++ b/lib/stdlib/src/filelib.erl
@@ -25,6 +25,7 @@
-export([wildcard/3, is_dir/2, is_file/2, is_regular/2]).
-export([fold_files/6, last_modified/2, file_size/2]).
-export([find_file/2, find_file/3, find_source/1, find_source/2, find_source/3]).
+-export([safe_relative_path/2]).
%% For debugging/testing.
-export([compile_wildcard/1]).
@@ -333,6 +334,7 @@ match_part([_|_], []) ->
false.
will_always_match([accept]) -> true;
+will_always_match([double_star]) -> true;
will_always_match(_) -> false.
prepare_base(Base0) ->
@@ -340,22 +342,33 @@ prepare_base(Base0) ->
"x"++Base2 = lists:reverse(Base1),
lists:reverse(Base2).
-do_double_star(Base, [H|T], Rest, Result, Mod, Root) ->
+do_double_star(Base, [H|T], Patterns, Result0, Mod, Root) ->
Full = case Root of
- false -> filename:join(Base, H);
- true -> H
- end,
+ false -> filename:join(Base, H);
+ true -> H
+ end,
Result1 = case do_list_dir(Full, Mod) of
- {ok, Files} ->
- do_double_star(Full, Files, Rest, Result, Mod, false);
- _ -> Result
- end,
- Result2 = case Root andalso Rest == [] of
- true -> Result1;
- false -> do_wildcard_3(Full, Rest, Result1, Mod)
- end,
- do_double_star(Base, T, Rest, Result2, Mod, Root);
-do_double_star(_Base, [], _Rest, Result, _Mod, _Root) ->
+ {ok, Files} ->
+ do_double_star(Full, Files, Patterns, Result0, Mod, false);
+ _ -> Result0
+ end,
+ Result2 = case Patterns of
+ %% The root is never included in the result.
+ _ when Root -> Result1;
+
+ %% An empty pattern includes all results (except the root).
+ [] -> [Full | Result1];
+
+ %% Otherwise we check if the current entry matches
+ %% and continue recursively.
+ [Pattern | Rest] ->
+ case match_part(Pattern, H) of
+ true -> do_wildcard_2([Full], Rest, Result1, Mod);
+ false -> Result1
+ end
+ end,
+ do_double_star(Base, T, Patterns, Result2, Mod, Root);
+do_double_star(_Base, [], _Patterns, Result, _Mod, _Root) ->
Result.
do_star(Pattern, [_|Rest]=File) ->
@@ -706,3 +719,71 @@ find_regular_file([File|Files]) ->
true -> {ok, File};
false -> find_regular_file(Files)
end.
+
+-spec safe_relative_path(Filename, Cwd) -> unsafe | SafeFilename when
+ Filename :: filename_all(),
+ Cwd :: filename_all(),
+ SafeFilename :: filename_all().
+
+safe_relative_path(Path, Cwd) ->
+ case filename:pathtype(Path) of
+ relative -> safe_relative_path(filename:split(Path), Cwd, [], "");
+ _ -> unsafe
+ end.
+
+safe_relative_path([], _Cwd, _PrevLinks, Acc) ->
+ Acc;
+
+safe_relative_path([Segment | Segments], Cwd, PrevLinks, Acc) ->
+ AccSegment = join(Acc, Segment),
+ case safe_relative_path(AccSegment) of
+ unsafe ->
+ unsafe;
+ SafeAccSegment ->
+ case file:read_link(join(Cwd, SafeAccSegment)) of
+ {ok, LinkPath} ->
+ case lists:member(LinkPath, PrevLinks) of
+ true ->
+ unsafe;
+ false ->
+ case safe_relative_path(filename:split(LinkPath), Cwd, [LinkPath | PrevLinks], Acc) of
+ unsafe -> unsafe;
+ NewAcc -> safe_relative_path(Segments, Cwd, [], NewAcc)
+ end
+ end;
+ {error, _} ->
+ safe_relative_path(Segments, Cwd, PrevLinks, SafeAccSegment)
+ end
+ end.
+
+join([], Path) -> Path;
+join(Left, Right) -> filename:join(Left, Right).
+
+safe_relative_path(Path) ->
+ case filename:pathtype(Path) of
+ relative ->
+ Cs0 = filename:split(Path),
+ safe_relative_path_1(Cs0, []);
+ _ ->
+ unsafe
+ end.
+
+safe_relative_path_1(["."|T], Acc) ->
+ safe_relative_path_1(T, Acc);
+safe_relative_path_1([<<".">>|T], Acc) ->
+ safe_relative_path_1(T, Acc);
+safe_relative_path_1([".."|T], Acc) ->
+ climb(T, Acc);
+safe_relative_path_1([<<"..">>|T], Acc) ->
+ climb(T, Acc);
+safe_relative_path_1([H|T], Acc) ->
+ safe_relative_path_1(T, [H|Acc]);
+safe_relative_path_1([], []) ->
+ [];
+safe_relative_path_1([], Acc) ->
+ filename:join(lists:reverse(Acc)).
+
+climb(_, []) ->
+ unsafe;
+climb(T, [_|Acc]) ->
+ safe_relative_path_1(T, Acc). \ No newline at end of file
diff --git a/lib/stdlib/src/filename.erl b/lib/stdlib/src/filename.erl
index b7b7b562ab..b6df99621f 100644
--- a/lib/stdlib/src/filename.erl
+++ b/lib/stdlib/src/filename.erl
@@ -19,8 +19,8 @@
%%
-module(filename).
--deprecated({find_src,1,next_major_release}).
--deprecated({find_src,2,next_major_release}).
+-deprecated([{find_src,'_',"use filelib:find_source/1,3 instead"}]).
+-deprecated([{safe_relative_path,1,"use filelib:safe_relative_path/2 instead"}]).
%% Purpose: Provides generic manipulation of filenames.
%%
diff --git a/lib/stdlib/src/gen.erl b/lib/stdlib/src/gen.erl
index a7f743bd4c..be14665d80 100644
--- a/lib/stdlib/src/gen.erl
+++ b/lib/stdlib/src/gen.erl
@@ -28,7 +28,9 @@
%%%-----------------------------------------------------------------
-export([start/5, start/6, debug_options/2, hibernate_after/1,
name/1, unregister_name/1, get_proc_name/1, get_parent/0,
- call/3, call/4, reply/2, stop/1, stop/3]).
+ call/3, call/4, reply/2,
+ send_request/3, wait_response/2, check_response/2,
+ stop/1, stop/3]).
-export([init_it/6, init_it/7]).
@@ -38,7 +40,7 @@
%%-----------------------------------------------------------------
--type linkage() :: 'link' | 'nolink'.
+-type linkage() :: 'monitor' | 'link' | 'nolink'.
-type emgr_name() :: {'local', atom()}
| {'global', term()}
| {'via', Module :: module(), Name :: term()}.
@@ -53,6 +55,11 @@
| {'spawn_opt', [proc_lib:spawn_option()]}.
-type options() :: [option()].
+-type server_ref() :: pid() | atom() | {atom(), node()}
+ | {global, term()} | {via, module(), term()}.
+
+-type request_id() :: term().
+
%%-----------------------------------------------------------------
%% Starts a generic process.
%% start(GenMod, LinkP, Mod, Args, Options)
@@ -95,6 +102,13 @@ do_spawn(GenMod, link, Mod, Args, Options) ->
[GenMod, self(), self(), Mod, Args, Options],
Time,
spawn_opts(Options));
+do_spawn(GenMod, monitor, Mod, Args, Options) ->
+ Time = timeout(Options),
+ Ret = proc_lib:start_monitor(?MODULE, init_it,
+ [GenMod, self(), self(), Mod, Args, Options],
+ Time,
+ spawn_opts(Options)),
+ monitor_return(Ret);
do_spawn(GenMod, _, Mod, Args, Options) ->
Time = timeout(Options),
proc_lib:start(?MODULE, init_it,
@@ -108,6 +122,13 @@ do_spawn(GenMod, link, Name, Mod, Args, Options) ->
[GenMod, self(), self(), Name, Mod, Args, Options],
Time,
spawn_opts(Options));
+do_spawn(GenMod, monitor, Name, Mod, Args, Options) ->
+ Time = timeout(Options),
+ Ret = proc_lib:start_monitor(?MODULE, init_it,
+ [GenMod, self(), self(), Name, Mod, Args, Options],
+ Time,
+ spawn_opts(Options)),
+ monitor_return(Ret);
do_spawn(GenMod, _, Name, Mod, Args, Options) ->
Time = timeout(Options),
proc_lib:start(?MODULE, init_it,
@@ -115,6 +136,26 @@ do_spawn(GenMod, _, Name, Mod, Args, Options) ->
Time,
spawn_opts(Options)).
+
+%%
+%% Adjust monitor returns for OTP gen behaviours...
+%%
+%% If an OTP behaviour is introduced that 'init_ack's
+%% other results, this has code has to be moved out
+%% into all behaviours as well as adjusted...
+%%
+monitor_return({{ok, Pid}, Mon}) when is_pid(Pid), is_reference(Mon) ->
+ %% Successful start_monitor()...
+ {ok, {Pid, Mon}};
+monitor_return({Error, Mon}) when is_reference(Mon) ->
+ %% Failure; wait for spawned process to terminate
+ %% and release resources, then return the error...
+ receive
+ {'DOWN', Mon, process, _Pid, _Reason} ->
+ ok
+ end,
+ Error.
+
%%-----------------------------------------------------------------
%% Initiate the new process.
%% Register the name using the Rfunc function
@@ -139,7 +180,7 @@ init_it2(GenMod, Starter, Parent, Name, Mod, Args, Options) ->
%%-----------------------------------------------------------------
%% Makes a synchronous call to a generic process.
%% Request is sent to the Pid, and the response must be
-%% {Tag, _, Reply}.
+%% {Tag, Reply}.
%%-----------------------------------------------------------------
%%% New call function which uses the new monitor BIF
@@ -192,6 +233,56 @@ get_node(Process) ->
node(Process)
end.
+-spec send_request(Name::server_ref(), Label::term(), Request::term()) -> request_id().
+send_request(Process, Label, Request) when is_pid(Process) ->
+ do_send_request(Process, Label, Request);
+send_request(Process, Label, Request) ->
+ Fun = fun(Pid) -> do_send_request(Pid, Label, Request) end,
+ try do_for_proc(Process, Fun)
+ catch exit:Reason ->
+ %% Make send_request async and fake a down message
+ Mref = erlang:make_ref(),
+ self() ! {'DOWN', Mref, process, Process, Reason},
+ Mref
+ end.
+
+do_send_request(Process, Label, Request) ->
+ Mref = erlang:monitor(process, Process),
+ erlang:send(Process, {Label, {self(), {'$gen_request_id', Mref}}, Request}, [noconnect]),
+ Mref.
+
+%%
+%% Wait for a reply to the client.
+%% Note: if timeout is returned monitors are kept.
+
+-spec wait_response(RequestId::request_id(), timeout()) ->
+ {reply, Reply::term()} | 'timeout' | {error, {term(), server_ref()}}.
+wait_response(Mref, Timeout)
+ when is_reference(Mref) ->
+ receive
+ {{'$gen_request_id', Mref}, Reply} ->
+ erlang:demonitor(Mref, [flush]),
+ {reply, Reply};
+ {'DOWN', Mref, _, Object, Reason} ->
+ {error, {Reason, Object}}
+ after Timeout ->
+ timeout
+ end.
+
+-spec check_response(RequestId::term(), Key::request_id()) ->
+ {reply, Reply::term()} | 'no_reply' | {error, {term(), server_ref()}}.
+check_response(Msg, Mref)
+ when is_reference(Mref) ->
+ case Msg of
+ {{'$gen_request_id', Mref}, Reply} ->
+ erlang:demonitor(Mref, [flush]),
+ {reply, Reply};
+ {'DOWN', Mref, _, Object, Reason} ->
+ {error, {Reason, Object}};
+ _ ->
+ no_reply
+ end.
+
%%
%% Send a reply to the client.
%%
diff --git a/lib/stdlib/src/gen_event.erl b/lib/stdlib/src/gen_event.erl
index 8213282867..8024221cab 100644
--- a/lib/stdlib/src/gen_event.erl
+++ b/lib/stdlib/src/gen_event.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2018. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2019. 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.
@@ -31,13 +31,20 @@
%%% Re-written by Joe with new functional interface !
%%% Modified by Martin - uses proc_lib, sys and gen!
+%%%
+%%% NOTE: If init_ack() return values are modified, see comment
+%%% above monitor_return() in gen.erl!
+%%%
-export([start/0, start/1, start/2,
start_link/0, start_link/1, start_link/2,
+ start_monitor/0, start_monitor/1, start_monitor/2,
stop/1, stop/3,
notify/2, sync_notify/2,
add_handler/3, add_sup_handler/3, delete_handler/3, swap_handler/3,
- swap_sup_handler/3, which_handlers/1, call/3, call/4, wake_hib/5]).
+ swap_sup_handler/3, which_handlers/1, call/3, call/4,
+ send_request/3, wait_response/2, check_response/2,
+ wake_hib/5]).
-export([init_it/6,
system_continue/3,
@@ -48,7 +55,7 @@
format_status/2]).
%% logger callback
--export([format_log/1]).
+-export([format_log/1, format_log/2]).
-export_type([handler/0, handler_args/0, add_handler_ret/0,
del_handler_ret/0]).
@@ -128,11 +135,13 @@
| {'logfile', string()}.
-type option() :: {'timeout', timeout()}
| {'debug', [debug_flag()]}
- | {'spawn_opt', [proc_lib:spawn_option()]}
+ | {'spawn_opt', [proc_lib:start_spawn_option()]}
| {'hibernate_after', timeout()}.
-type emgr_ref() :: atom() | {atom(), atom()} | {'global', term()}
| {'via', atom(), term()} | pid().
-type start_ret() :: {'ok', pid()} | {'error', term()}.
+-type start_mon_ret() :: {'ok', {pid(),reference()}} | {'error', term()}.
+-type request_id() :: term().
%%---------------------------------------------------------------------------
@@ -183,6 +192,20 @@ start_link(Options) when is_list(Options) ->
start_link(Name, Options) ->
gen:start(?MODULE, link, Name, ?NO_CALLBACK, [], Options).
+-spec start_monitor() -> start_mon_ret().
+start_monitor() ->
+ gen:start(?MODULE, monitor, ?NO_CALLBACK, [], []).
+
+-spec start_monitor(emgr_name() | [option()]) -> start_mon_ret().
+start_monitor(Name) when is_tuple(Name) ->
+ gen:start(?MODULE, monitor, Name, ?NO_CALLBACK, [], []);
+start_monitor(Options) when is_list(Options) ->
+ gen:start(?MODULE, monitor, ?NO_CALLBACK, [], Options).
+
+-spec start_monitor(emgr_name(), [option()]) -> start_mon_ret().
+start_monitor(Name, Options) ->
+ gen:start(?MODULE, monitor, Name, ?NO_CALLBACK, [], Options).
+
%% -spec init_it(pid(), 'self' | pid(), emgr_name(), module(), [term()], [_]) ->
init_it(Starter, self, Name, Mod, Args, Options) ->
init_it(Starter, self(), Name, Mod, Args, Options);
@@ -213,6 +236,26 @@ call(M, Handler, Query) -> call1(M, Handler, Query).
-spec call(emgr_ref(), handler(), term(), timeout()) -> term().
call(M, Handler, Query, Timeout) -> call1(M, Handler, Query, Timeout).
+-spec send_request(emgr_ref(), handler(), term()) -> request_id().
+send_request(M, Handler, Query) ->
+ gen:send_request(M, self(), {call, Handler, Query}).
+
+-spec wait_response(RequestId::request_id(), timeout()) ->
+ {reply, Reply::term()} | 'timeout' | {error, {Reason::term(), emgr_ref()}}.
+wait_response(RequestId, Timeout) ->
+ case gen:wait_response(RequestId, Timeout) of
+ {reply, {error, _} = Err} -> Err;
+ Return -> Return
+ end.
+
+-spec check_response(Msg::term(), RequestId::request_id()) ->
+ {reply, Reply::term()} | 'no_reply' | {error, {Reason::term(), emgr_ref()}}.
+check_response(Msg, RequestId) ->
+ case gen:check_response(Msg, RequestId) of
+ {reply, {error, _} = Err} -> Err;
+ Return -> Return
+ end.
+
-spec delete_handler(emgr_ref(), handler(), term()) -> term().
delete_handler(M, Handler, Args) -> rpc(M, {delete_handler, Handler, Args}).
@@ -590,8 +633,10 @@ server_update(Handler1, Func, Event, SName) ->
module=>Mod1,
message=>Event},
#{domain=>[otp],
- report_cb=>fun gen_event:format_log/1,
- error_logger=>#{tag=>warning_msg}}), % warningmap??
+ report_cb=>fun gen_event:format_log/2,
+ error_logger=>
+ #{tag=>warning_msg, % warningmap??
+ report_cb=>fun gen_event:format_log/1}}),
{ok, Handler1};
Other ->
do_terminate(Mod1, Handler1, {error, Other}, State,
@@ -752,46 +797,165 @@ report_error(Handler, Reason, State, LastIn, SName) ->
get(),State),
reason=>Reason},
#{domain=>[otp],
- report_cb=>fun gen_event:format_log/1,
- error_logger=>#{tag=>error}}).
-
-format_log(#{label:={gen_event,terminate},
- handler:=Handler,
- name:=SName,
- last_message:=LastIn,
- state:=State,
- reason:=Reason}) ->
- Reason1 =
- case Reason of
- {'EXIT',{undef,[{M,F,A,L}|MFAs]}} ->
- case code:is_loaded(M) of
- false ->
- {'module could not be loaded',[{M,F,A,L}|MFAs]};
- _ ->
- case erlang:function_exported(M, F, length(A)) of
- true ->
- {undef,[{M,F,A,L}|MFAs]};
- false ->
- {'function not exported',[{M,F,A,L}|MFAs]}
- end
- end;
- {'EXIT',Why} ->
- Why;
- _ ->
- Reason
- end,
- {"** gen_event handler ~p crashed.~n"
- "** Was installed in ~tp~n"
- "** Last event was: ~tp~n"
- "** When handler state == ~tp~n"
- "** Reason == ~tp~n",
- [Handler,SName,LastIn,State,Reason1]};
-format_log(#{label:={gen_event,no_handle_info},
- module:=Mod,
- message:=Msg}) ->
- {"** Undefined handle_info in ~tp~n"
- "** Unhandled message: ~tp~n",
- [Mod, Msg]}.
+ report_cb=>fun gen_event:format_log/2,
+ error_logger=>#{tag=>error,
+ report_cb=>fun gen_event:format_log/1}}).
+
+%% format_log/1 is the report callback used by Logger handler
+%% error_logger only. It is kept for backwards compatibility with
+%% legacy error_logger event handlers. This function must always
+%% return {Format,Args} compatible with the arguments in this module's
+%% calls to error_logger prior to OTP-21.0.
+format_log(Report) ->
+ Depth = error_logger:get_format_depth(),
+ FormatOpts = #{chars_limit => unlimited,
+ depth => Depth,
+ single_line => false,
+ encoding => utf8},
+ format_log_multi(limit_report(Report, Depth), FormatOpts).
+
+limit_report(Report, unlimited) ->
+ Report;
+limit_report(#{label:={gen_event,terminate},
+ last_message:=LastIn,
+ state:=State,
+ reason:=Reason}=Report,
+ Depth) ->
+ Report#{last_message => io_lib:limit_term(LastIn, Depth),
+ state => io_lib:limit_term(State, Depth),
+ reason => io_lib:limit_term(Reason, Depth)};
+limit_report(#{label:={gen_event,no_handle_info},
+ message:=Msg}=Report,
+ Depth) ->
+ Report#{message => io_lib:limit_term(Msg, Depth)}.
+
+%% format_log/2 is the report callback for any Logger handler, except
+%% error_logger.
+format_log(Report, FormatOpts0) ->
+ Default = #{chars_limit => unlimited,
+ depth => unlimited,
+ single_line => false,
+ encoding => utf8},
+ FormatOpts = maps:merge(Default, FormatOpts0),
+ IoOpts =
+ case FormatOpts of
+ #{chars_limit:=unlimited} ->
+ [];
+ #{chars_limit:=Limit} ->
+ [{chars_limit,Limit}]
+ end,
+ {Format,Args} = format_log_single(Report, FormatOpts),
+ io_lib:format(Format, Args, IoOpts).
+
+format_log_single(#{label:={gen_event,terminate},
+ handler:=Handler,
+ name:=SName,
+ last_message:=LastIn,
+ state:=State,
+ reason:=Reason},
+ #{single_line:=true, depth:=Depth}=FormatOpts) ->
+ P = p(FormatOpts),
+ Reason1 = fix_reason(Reason),
+ Format1 = lists:append(["Generic event handler ",P," crashed. "
+ "Installed: ",P,". Last event: ",P,
+ ". State: ",P,". Reason: ",P,"."]),
+ Args1 =
+ case Depth of
+ unlimited ->
+ [Handler,SName,Reason1,LastIn,State];
+ _ ->
+ [Handler,Depth,SName,Depth,Reason1,Depth,
+ LastIn,Depth,State,Depth]
+ end,
+ {Format1, Args1};
+format_log_single(#{label:={gen_event,no_handle_info},
+ module:=Mod,
+ message:=Msg},
+ #{single_line:=true,depth:=Depth}=FormatOpts) ->
+ P = p(FormatOpts),
+ Format = lists:append(["Undefined handle_info in ",P,
+ ". Unhandled message: ",P,"."]),
+ Args =
+ case Depth of
+ unlimited ->
+ [Mod,Msg];
+ _ ->
+ [Mod,Depth,Msg,Depth]
+ end,
+ {Format,Args};
+format_log_single(Report,FormatOpts) ->
+ format_log_multi(Report,FormatOpts).
+
+format_log_multi(#{label:={gen_event,terminate},
+ handler:=Handler,
+ name:=SName,
+ last_message:=LastIn,
+ state:=State,
+ reason:=Reason},
+ #{depth:=Depth}=FormatOpts) ->
+ Reason1 = fix_reason(Reason),
+ P = p(FormatOpts),
+ Format =
+ lists:append(["** gen_event handler ",P," crashed.\n",
+ "** Was installed in ",P,"\n",
+ "** Last event was: ",P,"\n",
+ "** When handler state == ",P,"\n",
+ "** Reason == ",P,"\n"]),
+ Args =
+ case Depth of
+ unlimited ->
+ [Handler,SName,LastIn,State,Reason1];
+ _ ->
+ [Handler,Depth,SName,Depth,LastIn,Depth,State,Depth,
+ Reason1,Depth]
+ end,
+ {Format,Args};
+format_log_multi(#{label:={gen_event,no_handle_info},
+ module:=Mod,
+ message:=Msg},
+ #{depth:=Depth}=FormatOpts) ->
+ P = p(FormatOpts),
+ Format =
+ "** Undefined handle_info in ~p\n"
+ "** Unhandled message: "++P++"\n",
+ Args =
+ case Depth of
+ unlimited ->
+ [Mod,Msg];
+ _ ->
+ [Mod,Msg,Depth]
+ end,
+ {Format,Args}.
+
+fix_reason({'EXIT',{undef,[{M,F,A,_L}|_]=MFAs}=Reason}) ->
+ case code:is_loaded(M) of
+ false ->
+ {'module could not be loaded',MFAs};
+ _ ->
+ case erlang:function_exported(M, F, length(A)) of
+ true ->
+ Reason;
+ false ->
+ {'function not exported',MFAs}
+ end
+ end;
+fix_reason({'EXIT',Reason}) ->
+ Reason;
+fix_reason(Reason) ->
+ Reason.
+
+p(#{single_line:=Single,depth:=Depth,encoding:=Enc}) ->
+ "~"++single(Single)++mod(Enc)++p(Depth);
+p(unlimited) ->
+ "p";
+p(_Depth) ->
+ "P".
+
+single(true) -> "0";
+single(false) -> "".
+
+mod(latin1) -> "";
+mod(_) -> "t".
handler(Handler) when not Handler#handler.id ->
Handler#handler.module;
diff --git a/lib/stdlib/src/gen_fsm.erl b/lib/stdlib/src/gen_fsm.erl
index 1e18710738..f4752c37d4 100644
--- a/lib/stdlib/src/gen_fsm.erl
+++ b/lib/stdlib/src/gen_fsm.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2018. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2019. 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.
@@ -127,27 +127,9 @@
format_status/2]).
%% logger callback
--export([format_log/1]).
-
--deprecated({start, 3, eventually}).
--deprecated({start, 4, eventually}).
--deprecated({start_link, 3, eventually}).
--deprecated({start_link, 4, eventually}).
--deprecated({stop, 1, eventually}).
--deprecated({stop, 3, eventually}).
--deprecated({send_event, 2, eventually}).
--deprecated({sync_send_event, 2, eventually}).
--deprecated({sync_send_event, 3, eventually}).
--deprecated({send_all_state_event, 2, eventually}).
--deprecated({sync_send_all_state_event, 2, eventually}).
--deprecated({sync_send_all_state_event, 3, eventually}).
--deprecated({reply, 2, eventually}).
--deprecated({start_timer, 2, eventually}).
--deprecated({send_event_after, 2, eventually}).
--deprecated({cancel_timer, 1, eventually}).
--deprecated({enter_loop, 4, eventually}).
--deprecated({enter_loop, 5, eventually}).
--deprecated({enter_loop, 6, eventually}).
+-export([format_log/1, format_log/2]).
+
+-deprecated({'_','_', "use the 'gen_statem' module instead"}).
%%% ---------------------------------------------------
%%% Interface functions.
@@ -517,8 +499,10 @@ handle_msg(Msg, Parent, Name, StateName, StateData, Mod, _Time, HibernateAfterTi
module=>Mod,
message=>Msg},
#{domain=>[otp],
- report_cb=>fun gen_fsm:format_log/1,
- error_logger=>#{tag=>warning_msg}}),
+ report_cb=>fun gen_fsm:format_log/2,
+ error_logger=>
+ #{tag=>warning_msg,
+ report_cb=>fun gen_fsm:format_log/1}}),
loop(Parent, Name, StateName, StateData, Mod, infinity, HibernateAfterTimeout, []);
{'EXIT', What} ->
terminate(What, Name, From, Msg, Mod, StateName, StateData, []);
@@ -634,8 +618,9 @@ error_info(Reason, Name, From, Msg, StateName, StateData, Debug) ->
reason=>Reason,
client_info=>client_stacktrace(From)},
#{domain=>[otp],
- report_cb=>fun gen_fsm:format_log/1,
- error_logger=>#{tag=>error}}),
+ report_cb=>fun gen_fsm:format_log/2,
+ error_logger=>#{tag=>error,
+ report_cb=>fun gen_fsm:format_log/1}}),
ok.
client_stacktrace(undefined) ->
@@ -655,70 +640,197 @@ client_stacktrace(Pid) when is_pid(Pid) ->
{Pid,remote}.
-format_log(#{label:={gen_fsm,terminate},
- name:=Name,
- last_message:=Msg,
- state_name:=StateName,
- state_data:=StateData,
- log:=Log,
- reason:=Reason,
- client_info:=ClientInfo}) ->
- Reason1 =
- case Reason of
- {undef,[{M,F,A,L}|MFAs]} ->
- case code:is_loaded(M) of
- false ->
- {'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,L}|MFAs]}
- end
- end;
- _ ->
- Reason
- end,
- {ClientFmt,ClientArgs} = format_client_log(ClientInfo),
- {"** State machine ~tp terminating \n" ++
- get_msg_str(Msg) ++
- "** When State == ~tp~n"
- "** Data == ~tp~n"
- "** Reason for termination ==~n** ~tp~n" ++
+%% format_log/1 is the report callback used by Logger handler
+%% error_logger only. It is kept for backwards compatibility with
+%% legacy error_logger event handlers. This function must always
+%% return {Format,Args} compatible with the arguments in this module's
+%% calls to error_logger prior to OTP-21.0.
+format_log(Report) ->
+ Depth = error_logger:get_format_depth(),
+ FormatOpts = #{chars_limit => unlimited,
+ depth => Depth,
+ single_line => false,
+ encoding => utf8},
+ format_log_multi(limit_report(Report, Depth), FormatOpts).
+
+limit_report(Report, unlimited) ->
+ Report;
+limit_report(#{label:={gen_fsm,terminate},
+ last_message:=Msg,
+ state_data:=StateData,
+ log:=Log,
+ reason:=Reason,
+ client_info:=ClientInfo}=Report,
+ Depth) ->
+ Report#{last_message=>io_lib:limit_term(Msg, Depth),
+ state_data=>io_lib:limit_term(StateData, Depth),
+ log=>[io_lib:limit_term(L, Depth) || L <- Log],
+ reason=>io_lib:limit_term(Reason, Depth),
+ client_info=>limit_client_report(ClientInfo, Depth)};
+limit_report(#{label:={gen_fsm,no_handle_info},
+ message:=Msg}=Report, Depth) ->
+ Report#{message=>io_lib:limit_term(Msg, Depth)}.
+
+limit_client_report({From,{Name,Stacktrace}}, Depth) ->
+ {From,{Name,io_lib:limit_term(Stacktrace, Depth)}};
+limit_client_report(Client, _) ->
+ Client.
+
+%% format_log/2 is the report callback for any Logger handler, except
+%% error_logger.
+format_log(Report, FormatOpts0) ->
+ Default = #{chars_limit => unlimited,
+ depth => unlimited,
+ single_line => false,
+ encoding => utf8},
+ FormatOpts = maps:merge(Default, FormatOpts0),
+ IoOpts =
+ case FormatOpts of
+ #{chars_limit:=unlimited} ->
+ [];
+ #{chars_limit:=Limit} ->
+ [{chars_limit,Limit}]
+ end,
+ {Format,Args} = format_log_single(Report, FormatOpts),
+ io_lib:format(Format, Args, IoOpts).
+
+format_log_single(#{label:={gen_fsm,terminate},
+ name:=Name,
+ last_message:=Msg,
+ state_name:=StateName,
+ state_data:=StateData,
+ log:=Log,
+ reason:=Reason,
+ client_info:=ClientInfo},
+ #{single_line:=true,depth:=Depth}=FormatOpts) ->
+ P = p(FormatOpts),
+ FixedReason = fix_reason(Reason),
+ {ClientFmt,ClientArgs} = format_client_log_single(ClientInfo, P, Depth),
+ Format =
+ lists:append(
+ ["State machine ",P," terminating. Reason: ",P,
+ ". Last event: ",P,
+ ". State: ",P,
+ ". Data: ",P,
+ case Log of
+ [] -> "";
+ _ -> ". Log: "++P
+ end,
+ "."]),
+ Args0 =
+ [Name,FixedReason,get_msg(Msg),StateName,StateData] ++
+ case Log of
+ [] -> [];
+ _ -> [Log]
+ end,
+ Args = case Depth of
+ unlimited ->
+ Args0;
+ _ ->
+ lists:flatmap(fun(A) -> [A, Depth] end, Args0)
+ end,
+ {Format++ClientFmt, Args++ClientArgs};
+format_log_single(#{label:={gen_fsm,no_handle_info},
+ module:=Mod,
+ message:=Msg},
+ #{single_line:=true,depth:=Depth}=FormatOpts) ->
+ P = p(FormatOpts),
+ Format = lists:append(["Undefined handle_info in ",P,
+ ". Unhandled message: ",P,"."]),
+ Args =
+ case Depth of
+ unlimited ->
+ [Mod,Msg];
+ _ ->
+ [Mod,Depth,Msg,Depth]
+ end,
+ {Format,Args};
+format_log_single(Report, FormatOpts) ->
+ format_log_multi(Report, FormatOpts).
+
+format_log_multi(#{label:={gen_fsm,terminate},
+ name:=Name,
+ last_message:=Msg,
+ state_name:=StateName,
+ state_data:=StateData,
+ log:=Log,
+ reason:=Reason,
+ client_info:=ClientInfo},
+ #{depth:=Depth}=FormatOpts) ->
+ P = p(FormatOpts),
+ FixedReason = fix_reason(Reason),
+ {ClientFmt,ClientArgs} = format_client_log(ClientInfo, P, Depth),
+ Format =
+ lists:append(
+ ["** State machine ",P," terminating \n"++
+ get_msg_str(Msg, P)++
+ "** When State == ",P,"~n",
+ "** Data == ",P,"~n",
+ "** Reason for termination ==~n** ",P,"~n",
+ case Log of
+ [] -> [];
+ _ -> "** Log ==~n**"++P++"~n"
+ end]),
+ Args0 =
+ [Name|get_msg(Msg)] ++
+ [StateName,StateData,FixedReason |
case Log of
[] -> [];
- _ -> "** Log ==~n** ~tp~n"
- end ++ ClientFmt,
- [Name|error_logger:limit_term(get_msg(Msg))] ++
- [StateName,
- error_logger:limit_term(StateData),
- error_logger:limit_term(Reason1) |
- case Log of
- [] -> [];
- _ -> [[error_logger:limit_term(D) || D <- Log]]
- end] ++ ClientArgs};
-format_log(#{label:={gen_fsm,no_handle_info},
- module:=Mod,
- message:=Msg}) ->
- {"** Undefined handle_info in ~p~n"
- "** Unhandled message: ~tp~n",
- [Mod, error_logger:limit_term(Msg)]}.
-
-get_msg_str({'$gen_event', _Event}) ->
- "** Last event in was ~tp~n";
-get_msg_str({'$gen_sync_event', _From, _Event}) ->
- "** Last sync event in was ~tp from ~tw~n";
-get_msg_str({'$gen_all_state_event', _Event}) ->
- "** Last event in was ~tp (for all states)~n";
-get_msg_str({'$gen_sync_all_state_event', _From, _Event}) ->
- "** Last sync event in was ~tp (for all states) from ~tw~n";
-get_msg_str({timeout, _Ref, {'$gen_timer', _Msg}}) ->
- "** Last timer event in was ~tp~n";
-get_msg_str({timeout, _Ref, {'$gen_event', _Msg}}) ->
- "** Last timer event in was ~tp~n";
-get_msg_str(_Msg) ->
- "** Last message in was ~tp~n".
+ _ -> [Log]
+ end],
+ Args = case Depth of
+ unlimited ->
+ Args0;
+ _ ->
+ lists:flatmap(fun(A) -> [A, Depth] end, Args0)
+ end,
+ {Format++ClientFmt,Args++ClientArgs};
+format_log_multi(#{label:={gen_fsm,no_handle_info},
+ module:=Mod,
+ message:=Msg},
+ #{depth:=Depth}=FormatOpts) ->
+ P = p(FormatOpts),
+ Format =
+ "** Undefined handle_info in ~p~n"
+ "** Unhandled message: "++P++"~n",
+ Args =
+ case Depth of
+ unlimited ->
+ [Mod,Msg];
+ _ ->
+ [Mod,Msg,Depth]
+ end,
+ {Format,Args}.
+
+fix_reason({undef,[{M,F,A,L}|MFAs]}=Reason) ->
+ case code:is_loaded(M) of
+ false ->
+ {'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,L}|MFAs]}
+ end
+ end;
+fix_reason(Reason) ->
+ Reason.
+
+get_msg_str({'$gen_event', _Event}, P) ->
+ "** Last event in was "++P++"~n";
+get_msg_str({'$gen_sync_event', _From, _Event}, P) ->
+ "** Last sync event in was "++P++" from ~tw~n";
+get_msg_str({'$gen_all_state_event', _Event}, P) ->
+ "** Last event in was "++P++" (for all states)~n";
+get_msg_str({'$gen_sync_all_state_event', _From, _Event}, P) ->
+ "** Last sync event in was "++P++" (for all states) from "++P++"~n";
+get_msg_str({timeout, _Ref, {'$gen_timer', _Msg}}, P) ->
+ "** Last timer event in was "++P++"~n";
+get_msg_str({timeout, _Ref, {'$gen_event', _Msg}}, P) ->
+ "** Last timer event in was "++P++"~n";
+get_msg_str(_Msg, P) ->
+ "** Last message in was "++P++"~n".
get_msg({'$gen_event', Event}) -> [Event];
get_msg({'$gen_sync_event', {From,_Tag}, Event}) -> [Event,From];
@@ -728,16 +840,53 @@ get_msg({timeout, Ref, {'$gen_timer', Msg}}) -> [{timeout, Ref, Msg}];
get_msg({timeout, _Ref, {'$gen_event', Event}}) -> [Event];
get_msg(Msg) -> [Msg].
-format_client_log(undefined) ->
+format_client_log_single(undefined, _, _) ->
+ {"", []};
+format_client_log_single({Pid,dead}, _, _) ->
+ {" Client ~0p is dead.", [Pid]};
+format_client_log_single({Pid,remote}, _, _) ->
+ {" Client ~0p is remote on node ~0p.", [Pid,node(Pid)]};
+format_client_log_single({_Pid,{Name,Stacktrace0}}, P, Depth) ->
+ %% Minimize the stacktrace a bit for single line reports. This is
+ %% hopefully enough to point out the position.
+ Stacktrace = lists:sublist(Stacktrace0, 4),
+ Format = lists:append([" Client ",P," stacktrace: ",P,"."]),
+ Args = case Depth of
+ unlimited ->
+ [Name, Stacktrace];
+ _ ->
+ [Name, Depth, Stacktrace, Depth]
+ end,
+ {Format, Args}.
+
+format_client_log(undefined, _, _) ->
{"", []};
-format_client_log({From,dead}) ->
- {"** Client ~p is dead~n", [From]};
-format_client_log({From,remote}) ->
- {"** Client ~p is remote on node ~p~n", [From, node(From)]};
-format_client_log({_From,{Name,Stacktrace}}) ->
- {"** Client ~tp stacktrace~n"
- "** ~tp~n",
- [Name, error_logger:limit_term(Stacktrace)]}.
+format_client_log({Pid,dead}, _, _) ->
+ {"** Client ~p is dead~n", [Pid]};
+format_client_log({Pid,remote}, _, _) ->
+ {"** Client ~p is remote on node ~p~n", [Pid,node(Pid)]};
+format_client_log({_Pid,{Name,Stacktrace}}, P, Depth) ->
+ Format = lists:append(["** Client ",P," stacktrace~n** ",P,"~n"]),
+ Args = case Depth of
+ unlimited ->
+ [Name, Stacktrace];
+ _ ->
+ [Name, Depth, Stacktrace, Depth]
+ end,
+ {Format,Args}.
+
+p(#{single_line:=Single,depth:=Depth,encoding:=Enc}) ->
+ "~"++single(Single)++mod(Enc)++p(Depth);
+p(unlimited) ->
+ "p";
+p(_Depth) ->
+ "P".
+
+single(true) -> "0";
+single(false) -> "".
+
+mod(latin1) -> "";
+mod(_) -> "t".
%%-----------------------------------------------------------------
%% Status information
diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl
index c7b6406f54..e49961a5f0 100644
--- a/lib/stdlib/src/gen_server.erl
+++ b/lib/stdlib/src/gen_server.erl
@@ -19,6 +19,11 @@
%%
-module(gen_server).
+%%%
+%%% NOTE: If init_ack() return values are modified, see comment
+%%% above monitor_return() in gen.erl!
+%%%
+
%%% ---------------------------------------------------
%%%
%%% The idea behind THIS server is that the user module
@@ -89,8 +94,10 @@
%% API
-export([start/3, start/4,
start_link/3, start_link/4,
+ start_monitor/3, start_monitor/4,
stop/1, stop/3,
call/2, call/3,
+ send_request/2, wait_response/2, check_response/2,
cast/2, reply/2,
abcast/2, abcast/3,
multi_call/2, multi_call/3, multi_call/4,
@@ -105,7 +112,7 @@
format_status/2]).
%% logger callback
--export([format_log/1]).
+-export([format_log/1, format_log/2]).
%% Internal exports
-export([init_it/6]).
@@ -116,6 +123,16 @@
STACKTRACE(),
element(2, erlang:process_info(self(), current_stacktrace))).
+
+-type server_ref() ::
+ pid()
+ | (LocalName :: atom())
+ | {Name :: atom(), Node :: atom()}
+ | {'global', GlobalName :: term()}
+ | {'via', RegMod :: module(), ViaName :: term()}.
+
+-type request_id() :: term().
+
%%%=========================================================================
%%% API
%%%=========================================================================
@@ -188,6 +205,12 @@ start_link(Mod, Args, Options) ->
start_link(Name, Mod, Args, Options) ->
gen:start(?MODULE, link, Name, Mod, Args, Options).
+start_monitor(Mod, Args, Options) ->
+ gen:start(?MODULE, monitor, Mod, Args, Options).
+
+start_monitor(Name, Mod, Args, Options) ->
+ gen:start(?MODULE, monitor, Name, Mod, Args, Options).
+
%% -----------------------------------------------------------------
%% Stop a generic server and wait for it to terminate.
@@ -224,6 +247,25 @@ call(Name, Request, Timeout) ->
end.
%% -----------------------------------------------------------------
+%% Send a request to a generic server and return a Key which should be
+%% used with wait_response/2 or check_response/2 to fetch the
+%% result of the request.
+
+-spec send_request(Name::server_ref(), Request::term()) -> request_id().
+send_request(Name, Request) ->
+ gen:send_request(Name, '$gen_call', Request).
+
+-spec wait_response(RequestId::request_id(), timeout()) ->
+ {reply, Reply::term()} | 'timeout' | {error, {Reason::term(), server_ref()}}.
+wait_response(RequestId, Timeout) ->
+ gen:wait_response(RequestId, Timeout).
+
+-spec check_response(Msg::term(), RequestId::request_id()) ->
+ {reply, Reply::term()} | 'no_reply' | {error, {Reason::term(), server_ref()}}.
+check_response(Msg, RequestId) ->
+ gen:check_response(Msg, RequestId).
+
+%% -----------------------------------------------------------------
%% Make a cast to a generic server.
%% -----------------------------------------------------------------
cast({global,Name}, Request) ->
@@ -249,7 +291,8 @@ cast_msg(Request) -> {'$gen_cast',Request}.
%% Send a reply to the client.
%% -----------------------------------------------------------------
reply({To, Tag}, Reply) ->
- catch To ! {Tag, Reply}.
+ catch To ! {Tag, Reply},
+ ok.
%% -----------------------------------------------------------------
%% Asynchronous broadcast, returns nothing, it's just send 'n' pray
@@ -646,8 +689,10 @@ try_dispatch(Mod, Func, Msg, State) ->
module=>Mod,
message=>Msg},
#{domain=>[otp],
- report_cb=>fun gen_server:format_log/1,
- error_logger=>#{tag=>warning_msg}}),
+ report_cb=>fun gen_server:format_log/2,
+ error_logger=>
+ #{tag=>warning_msg,
+ report_cb=>fun gen_server:format_log/1}}),
{ok, {noreply, State}};
true ->
{'EXIT', error, R, Stacktrace}
@@ -894,8 +939,9 @@ error_info(Reason, Name, From, Msg, Mod, State, Debug) ->
reason=>Reason,
client_info=>client_stacktrace(From)},
#{domain=>[otp],
- report_cb=>fun gen_server:format_log/1,
- error_logger=>#{tag=>error}}),
+ report_cb=>fun gen_server:format_log/2,
+ error_logger=>#{tag=>error,
+ report_cb=>fun gen_server:format_log/1}}),
ok.
client_stacktrace(undefined) ->
@@ -914,63 +960,236 @@ client_stacktrace(From) when is_pid(From), node(From) =:= node() ->
client_stacktrace(From) when is_pid(From) ->
{From,remote}.
-format_log(#{label:={gen_server,terminate},
- name:=Name,
- last_message:=Msg,
- state:=State,
- log:=Log,
- reason:=Reason,
- client_info:=Client}) ->
- Reason1 =
- case Reason of
- {undef,[{M,F,A,L}|MFAs]} ->
- case code:is_loaded(M) of
- false ->
- {'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,L}|MFAs]}
- end
- end;
- _ ->
- Reason
- end,
- {ClientFmt,ClientArgs} = format_client_log(Client),
- [LimitedMsg,LimitedState,LimitedReason|LimitedLog] =
- [error_logger:limit_term(D) || D <- [Msg,State,Reason1|Log]],
- {"** Generic server ~tp terminating \n"
- "** Last message in was ~tp~n"
- "** When Server state == ~tp~n"
- "** Reason for termination ==~n** ~tp~n" ++
- case LimitedLog of
- [] -> [];
- _ -> "** Log ==~n** ~tp~n"
- end ++ ClientFmt,
- [Name, LimitedMsg, LimitedState, LimitedReason] ++
- case LimitedLog of
- [] -> [];
- _ -> [LimitedLog]
- end ++ ClientArgs};
-format_log(#{label:={gen_server,no_handle_info},
- module:=Mod,
- message:=Msg}) ->
- {"** Undefined handle_info in ~p~n"
- "** Unhandled message: ~tp~n",
- [Mod, error_logger:limit_term(Msg)]}.
-
-format_client_log(undefined) ->
+
+%% format_log/1 is the report callback used by Logger handler
+%% error_logger only. It is kept for backwards compatibility with
+%% legacy error_logger event handlers. This function must always
+%% return {Format,Args} compatible with the arguments in this module's
+%% calls to error_logger prior to OTP-21.0.
+format_log(Report) ->
+ Depth = error_logger:get_format_depth(),
+ FormatOpts = #{chars_limit => unlimited,
+ depth => Depth,
+ single_line => false,
+ encoding => utf8},
+ format_log_multi(limit_report(Report,Depth),FormatOpts).
+
+limit_report(Report,unlimited) ->
+ Report;
+limit_report(#{label:={gen_server,terminate},
+ last_message:=Msg,
+ state:=State,
+ log:=Log,
+ reason:=Reason,
+ client_info:=Client}=Report,
+ Depth) ->
+ Report#{last_message=>io_lib:limit_term(Msg,Depth),
+ state=>io_lib:limit_term(State,Depth),
+ log=>[io_lib:limit_term(L,Depth)||L<-Log],
+ reason=>io_lib:limit_term(Reason,Depth),
+ client_info=>limit_client_report(Client,Depth)};
+limit_report(#{label:={gen_server,no_handle_info},
+ message:=Msg}=Report,Depth) ->
+ Report#{message=>io_lib:limit_term(Msg,Depth)}.
+
+limit_client_report({From,{Name,Stacktrace}},Depth) ->
+ {From,{Name,io_lib:limit_term(Stacktrace,Depth)}};
+limit_client_report(Client,_) ->
+ Client.
+
+%% format_log/2 is the report callback for any Logger handler, except
+%% error_logger.
+format_log(Report, FormatOpts0) ->
+ Default = #{chars_limit => unlimited,
+ depth => unlimited,
+ single_line => false,
+ encoding => utf8},
+ FormatOpts = maps:merge(Default,FormatOpts0),
+ IoOpts =
+ case FormatOpts of
+ #{chars_limit:=unlimited} ->
+ [];
+ #{chars_limit:=Limit} ->
+ [{chars_limit,Limit}]
+ end,
+ {Format,Args} = format_log_single(Report, FormatOpts),
+ io_lib:format(Format, Args, IoOpts).
+
+format_log_single(#{label:={gen_server,terminate},
+ name:=Name,
+ last_message:=Msg,
+ state:=State,
+ log:=Log,
+ reason:=Reason,
+ client_info:=Client},
+ #{single_line:=true,depth:=Depth}=FormatOpts) ->
+ P = p(FormatOpts),
+ Format1 = lists:append(["Generic server ",P," terminating. Reason: ",P,
+ ". Last message: ", P, ". State: ",P,"."]),
+ {ServerLogFormat,ServerLogArgs} = format_server_log_single(Log,FormatOpts),
+ {ClientLogFormat,ClientLogArgs} = format_client_log_single(Client,FormatOpts),
+
+ Args1 =
+ case Depth of
+ unlimited ->
+ [Name,fix_reason(Reason),Msg,State];
+ _ ->
+ [Name,Depth,fix_reason(Reason),Depth,Msg,Depth,State,Depth]
+ end,
+ {Format1++ServerLogFormat++ClientLogFormat,
+ Args1++ServerLogArgs++ClientLogArgs};
+format_log_single(#{label:={gen_server,no_handle_info},
+ module:=Mod,
+ message:=Msg},
+ #{single_line:=true,depth:=Depth}=FormatOpts) ->
+ P = p(FormatOpts),
+ Format = lists:append(["Undefined handle_info in ",P,
+ ". Unhandled message: ",P,"."]),
+ Args =
+ case Depth of
+ unlimited ->
+ [Mod,Msg];
+ _ ->
+ [Mod,Depth,Msg,Depth]
+ end,
+ {Format,Args};
+format_log_single(Report,FormatOpts) ->
+ format_log_multi(Report,FormatOpts).
+
+format_log_multi(#{label:={gen_server,terminate},
+ name:=Name,
+ last_message:=Msg,
+ state:=State,
+ log:=Log,
+ reason:=Reason,
+ client_info:=Client},
+ #{depth:=Depth}=FormatOpts) ->
+ Reason1 = fix_reason(Reason),
+ {ClientFmt,ClientArgs} = format_client_log(Client,FormatOpts),
+ P = p(FormatOpts),
+ Format =
+ lists:append(
+ ["** Generic server ",P," terminating \n"
+ "** Last message in was ",P,"~n"
+ "** When Server state == ",P,"~n"
+ "** Reason for termination ==~n** ",P,"~n"] ++
+ case Log of
+ [] -> [];
+ _ -> ["** Log ==~n** ["|
+ lists:join(",~n ",lists:duplicate(length(Log),P))]++
+ ["]~n"]
+ end) ++ ClientFmt,
+ Args =
+ case Depth of
+ unlimited ->
+ [Name, Msg, State, Reason1] ++
+ case Log of
+ [] -> [];
+ _ -> Log
+ end ++ ClientArgs;
+ _ ->
+ [Name, Depth, Msg, Depth, State, Depth, Reason1, Depth] ++
+ case Log of
+ [] -> [];
+ _ -> lists:flatmap(fun(L) -> [L, Depth] end, Log)
+ end ++ ClientArgs
+ end,
+ {Format,Args};
+format_log_multi(#{label:={gen_server,no_handle_info},
+ module:=Mod,
+ message:=Msg},
+ #{depth:=Depth}=FormatOpts) ->
+ P = p(FormatOpts),
+ Format =
+ "** Undefined handle_info in ~p~n"
+ "** Unhandled message: "++P++"~n",
+ Args =
+ case Depth of
+ unlimited ->
+ [Mod,Msg];
+ _ ->
+ [Mod,Msg,Depth]
+ end,
+ {Format,Args}.
+
+fix_reason({undef,[{M,F,A,L}|MFAs]}=Reason) ->
+ case code:is_loaded(M) of
+ false ->
+ {'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,L}|MFAs]}
+ end
+ end;
+fix_reason(Reason) ->
+ Reason.
+
+format_server_log_single([],_) ->
+ {"",[]};
+format_server_log_single(Log,FormatOpts) ->
+ Args =
+ case maps:get(depth,FormatOpts) of
+ unlimited ->
+ [Log];
+ Depth ->
+ [Log, Depth]
+ end,
+ {" Log: "++p(FormatOpts),Args}.
+
+format_client_log_single(undefined,_) ->
+ {"",[]};
+format_client_log_single({From,dead},_) ->
+ {" Client ~0p is dead.",[From]};
+format_client_log_single({From,remote},_) ->
+ {" Client ~0p is remote on node ~0p.", [From, node(From)]};
+format_client_log_single({_From,{Name,Stacktrace0}},FormatOpts) ->
+ P = p(FormatOpts),
+ %% Minimize the stacktrace a bit for single line reports. This is
+ %% hopefully enough to point out the position.
+ Stacktrace = lists:sublist(Stacktrace0,4),
+ Args =
+ case maps:get(depth,FormatOpts) of
+ unlimited ->
+ [Name, Stacktrace];
+ Depth ->
+ [Name, Depth, Stacktrace, Depth]
+ end,
+ {" Client "++P++" stacktrace: "++P++".", Args}.
+
+format_client_log(undefined,_) ->
{"", []};
-format_client_log({From,dead}) ->
+format_client_log({From,dead},_) ->
{"** Client ~p is dead~n", [From]};
-format_client_log({From,remote}) ->
+format_client_log({From,remote},_) ->
{"** Client ~p is remote on node ~p~n", [From, node(From)]};
-format_client_log({_From,{Name,Stacktrace}}) ->
- {"** Client ~tp stacktrace~n"
- "** ~tp~n",
- [Name, error_logger:limit_term(Stacktrace)]}.
+format_client_log({_From,{Name,Stacktrace}},FormatOpts) ->
+ P = p(FormatOpts),
+ Format = lists:append(["** Client ",P," stacktrace~n",
+ "** ",P,"~n"]),
+ Args =
+ case maps:get(depth,FormatOpts) of
+ unlimited ->
+ [Name, Stacktrace];
+ Depth ->
+ [Name, Depth, Stacktrace, Depth]
+ end,
+ {Format,Args}.
+
+p(#{single_line:=Single,depth:=Depth,encoding:=Enc}) ->
+ "~"++single(Single)++mod(Enc)++p(Depth);
+p(unlimited) ->
+ "p";
+p(_Depth) ->
+ "P".
+
+single(true) -> "0";
+single(false) -> "".
+
+mod(latin1) -> "";
+mod(_) -> "t".
%%-----------------------------------------------------------------
%% Status information
diff --git a/lib/stdlib/src/gen_statem.erl b/lib/stdlib/src/gen_statem.erl
index 885c6ef031..acedd6daaa 100644
--- a/lib/stdlib/src/gen_statem.erl
+++ b/lib/stdlib/src/gen_statem.erl
@@ -21,11 +21,18 @@
-include("logger.hrl").
+%%%
+%%% NOTE: If init_ack() return values are modified, see comment
+%%% above monitor_return() in gen.erl!
+%%%
+
%% API
-export(
[start/3,start/4,start_link/3,start_link/4,
+ start_monitor/3,start_monitor/4,
stop/1,stop/3,
cast/2,call/2,call/3,
+ send_request/2,wait_response/1,wait_response/2,check_response/2,
enter_loop/4,enter_loop/5,enter_loop/6,
reply/1,reply/2]).
@@ -47,7 +54,7 @@
[wakeup_from_hibernate/3]).
%% logger callback
--export([format_log/1]).
+-export([format_log/1, format_log/2]).
%% Type exports for templates and callback modules
-export_type(
@@ -58,7 +65,8 @@
event_handler_result/1,
reply_action/0,
enter_action/0,
- action/0]).
+ action/0
+ ]).
%% Old types, not advertised
-export_type(
[state_function_result/0,
@@ -257,6 +265,7 @@
Replies :: [reply_action()] | reply_action(),
NewData :: data()}.
+-type request_id() :: term().
%% The state machine init function. It is called only once and
%% the server is not running until this function has returned
@@ -453,12 +462,16 @@ timeout_event_type(Type) ->
| {'via', RegMod :: module(), ViaName :: term()}.
-type start_opt() ::
{'timeout', Time :: timeout()}
- | {'spawn_opt', [proc_lib:spawn_option()]}
+ | {'spawn_opt', [proc_lib:start_spawn_option()]}
| enter_loop_opt().
-type start_ret() ::
{'ok', pid()}
| 'ignore'
| {'error', term()}.
+-type start_mon_ret() ::
+ {'ok', {pid(),reference()}}
+ | 'ignore'
+ | {'error', term()}.
-type enter_loop_opt() ::
{'hibernate_after', HibernateAfterTimeout :: timeout()}
| {'debug', Dbgs :: [sys:debug_option()]}.
@@ -493,6 +506,20 @@ start_link(Module, Args, Opts) ->
start_link(ServerName, Module, Args, Opts) ->
gen:start(?MODULE, link, ServerName, Module, Args, Opts).
+%% Start and monitor a state machine
+-spec start_monitor(
+ Module :: module(), Args :: term(), Opts :: [start_opt()]) ->
+ start_mon_ret().
+start_monitor(Module, Args, Opts) ->
+ gen:start(?MODULE, monitor, Module, Args, Opts).
+%%
+-spec start_monitor(
+ ServerName :: server_name(),
+ Module :: module(), Args :: term(), Opts :: [start_opt()]) ->
+ start_mon_ret().
+start_monitor(ServerName, Module, Args, Opts) ->
+ gen:start(?MODULE, monitor, ServerName, Module, Args, Opts).
+
%% Stop a state machine
-spec stop(ServerRef :: server_ref()) -> ok.
stop(ServerRef) ->
@@ -551,6 +578,26 @@ call(ServerRef, Request, {_, _} = Timeout) ->
call(ServerRef, Request, Timeout) ->
call_clean(ServerRef, Request, Timeout, Timeout).
+-spec send_request(ServerRef::server_ref(), Request::term()) ->
+ RequestId::request_id().
+send_request(Name, Request) ->
+ gen:send_request(Name, '$gen_call', Request).
+
+-spec wait_response(RequestId::request_id()) ->
+ {reply, Reply::term()} | {error, {term(), server_ref()}}.
+wait_response(RequestId) ->
+ gen:wait_response(RequestId, infinity).
+
+-spec wait_response(RequestId::request_id(), timeout()) ->
+ {reply, Reply::term()} | 'timeout' | {error, {term(), server_ref()}}.
+wait_response(RequestId, Timeout) ->
+ gen:wait_response(RequestId, Timeout).
+
+-spec check_response(Msg::term(), RequestId::request_id()) ->
+ {reply, Reply::term()} | 'no_reply' | {error, {term(), server_ref()}}.
+check_response(Msg, RequestId) ->
+ gen:check_response(Msg, RequestId).
+
%% Reply from a state machine callback to whom awaits in call/2
-spec reply([reply_action()] | reply_action()) -> ok.
reply({reply,From,Reply}) ->
@@ -2329,8 +2376,10 @@ error_info(
reason=>{Class,Reason,Stacktrace},
client_info=>client_stacktrace(Q)},
#{domain=>[otp],
- report_cb=>fun gen_statem:format_log/1,
- error_logger=>#{tag=>error}}).
+ report_cb=>fun gen_statem:format_log/2,
+ error_logger=>
+ #{tag=>error,
+ report_cb=>fun gen_statem:format_log/1}}).
client_stacktrace([]) ->
undefined;
@@ -2356,42 +2405,155 @@ client_stacktrace([_|_]) ->
undefined.
-format_log(#{label:={gen_statem,terminate},
- name:=Name,
- queue:=Q,
- postponed:=Postponed,
- callback_mode:=CallbackMode,
- state_enter:=StateEnter,
- state:=FmtData,
- timeouts:=Timeouts,
- log:=Log,
- reason:={Class,Reason,Stacktrace},
- client_info:=ClientInfo}) ->
- {FixedReason,FixedStacktrace} =
- case Stacktrace of
- [{M,F,Args,_}|ST]
- when Class =:= error, Reason =:= undef ->
- case code:is_loaded(M) of
- false ->
- {{'module could not be loaded',M},ST};
- _ ->
- Arity =
- if
- is_list(Args) ->
- length(Args);
- is_integer(Args) ->
- Args
- end,
- case erlang:function_exported(M, F, Arity) of
- true ->
- {Reason,Stacktrace};
- false ->
- {{'function not exported',{M,F,Arity}},ST}
- end
- end;
- _ -> {Reason,Stacktrace}
- end,
- {ClientFmt,ClientArgs} = format_client_log(ClientInfo),
+%% format_log/1 is the report callback used by Logger handler
+%% error_logger only. It is kept for backwards compatibility with
+%% legacy error_logger event handlers. This function must always
+%% return {Format,Args} compatible with the arguments in this module's
+%% calls to error_logger prior to OTP-21.0.
+format_log(Report) ->
+ Depth = error_logger:get_format_depth(),
+ FormatOpts = #{chars_limit => unlimited,
+ depth => Depth,
+ single_line => false,
+ encoding => utf8},
+ format_log_multi(limit_report(Report, Depth), FormatOpts).
+
+limit_report(Report, unlimited) ->
+ Report;
+limit_report(#{label:={gen_statem,terminate},
+ queue:=Q,
+ postponed:=Postponed,
+ state:=FmtData,
+ timeouts:=Timeouts,
+ log:=Log,
+ reason:={Class,Reason,Stacktrace},
+ client_info:=ClientInfo}=Report,
+ Depth) ->
+ Report#{queue =>
+ case Q of
+ [Event|Events] ->
+ [io_lib:limit_term(Event, Depth)
+ |io_lib:limit_term(Events, Depth)];
+ _ -> []
+ end,
+ postponed =>
+ case Postponed of
+ [] -> [];
+ _ -> io_lib:limit_term(Postponed, Depth)
+ end,
+ state => io_lib:limit_term(FmtData, Depth),
+ timeouts =>
+ case Timeouts of
+ {0,_} -> Timeouts;
+ _ -> io_lib:limit_term(Timeouts, Depth)
+ end,
+ log =>
+ case Log of
+ [] -> [];
+ _ -> [io_lib:limit_term(T, Depth) || T <- Log]
+ end,
+ reason =>
+ {Class,
+ io_lib:limit_term(Reason, Depth),
+ io_lib:limit_term(Stacktrace, Depth)},
+ client_info => limit_client_info(ClientInfo, Depth)}.
+
+
+limit_client_info({Pid,{Name,Stacktrace}}, Depth) ->
+ {Pid,{Name,io_lib:limit_term(Stacktrace, Depth)}};
+limit_client_info(Client, _Depth) ->
+ Client.
+
+%% format_log/2 is the report callback for any Logger handler, except
+%% error_logger.
+format_log(Report, FormatOpts0) ->
+ Default = #{chars_limit => unlimited,
+ depth => unlimited,
+ single_line => false,
+ encoding => utf8},
+ FormatOpts = maps:merge(Default,FormatOpts0),
+ IoOpts =
+ case FormatOpts of
+ #{chars_limit:=unlimited} ->
+ [];
+ #{chars_limit:=Limit} ->
+ [{chars_limit,Limit}]
+ end,
+ {Format,Args} = format_log_single(Report, FormatOpts),
+ io_lib:format(Format, Args, IoOpts).
+
+format_log_single(#{label:={gen_statem,terminate},
+ name:=Name,
+ queue:=Q,
+ %% postponed
+ %% callback_mode
+ %% state_enter
+ state:=FmtData,
+ %% timeouts
+ log:=Log,
+ reason:={Class,Reason,Stacktrace},
+ client_info:=ClientInfo},
+ #{single_line:=true,depth:=Depth}=FormatOpts) ->
+ P = p(FormatOpts),
+ {FixedReason,FixedStacktrace} = fix_reason(Class, Reason, Stacktrace),
+ {ClientFmt,ClientArgs} = format_client_log_single(ClientInfo, P, Depth),
+ Format =
+ lists:append(
+ ["State machine ",P," terminating. Reason: ",P,
+ case FixedStacktrace of
+ [] -> "";
+ _ -> ". Stack: "++P
+ end,
+ case Q of
+ [] -> "";
+ _ -> ". Last event: "++P
+ end,
+ ". State: ",P,
+ case Log of
+ [] -> "";
+ _ -> ". Log: "++P
+ end,
+ "."]),
+ Args0 =
+ [Name,FixedReason] ++
+ case FixedStacktrace of
+ [] -> [];
+ _ -> [FixedStacktrace]
+ end ++
+ case Q of
+ [] -> [];
+ [Event|_] -> [Event]
+ end ++
+ [FmtData] ++
+ case Log of
+ [] -> [];
+ _ -> [Log]
+ end,
+ Args = case Depth of
+ unlimited ->
+ Args0;
+ _ ->
+ lists:flatmap(fun(A) -> [A, Depth] end, Args0)
+ end,
+ {Format++ClientFmt, Args++ClientArgs};
+format_log_single(Report, FormatOpts) ->
+ format_log_multi(Report, FormatOpts).
+
+format_log_multi(#{label:={gen_statem,terminate},
+ name:=Name,
+ queue:=Q,
+ postponed:=Postponed,
+ callback_mode:=CallbackMode,
+ state_enter:=StateEnter,
+ state:=FmtData,
+ timeouts:=Timeouts,
+ log:=Log,
+ reason:={Class,Reason,Stacktrace},
+ client_info:=ClientInfo},
+ #{depth:=Depth}=FormatOpts) ->
+ P = p(FormatOpts),
+ {FixedReason,FixedStacktrace} = fix_reason(Class, Reason, Stacktrace),
+ {ClientFmt,ClientArgs} = format_client_log(ClientInfo, P, Depth),
CBMode =
case StateEnter of
true ->
@@ -2399,74 +2561,145 @@ format_log(#{label:={gen_statem,terminate},
false ->
CallbackMode
end,
- {"** State machine ~tp terminating~n" ++
- case Q of
- [] -> "";
- _ -> "** Last event = ~tp~n"
- end ++
- "** When server state = ~tp~n" ++
- "** Reason for termination = ~w:~tp~n" ++
- "** Callback mode = ~p~n" ++
+ Format =
+ lists:append(
+ ["** State machine ",P," terminating~n",
+ case Q of
+ [] -> "";
+ _ -> "** Last event = "++P++"~n"
+ end,
+ "** When server state = ",P,"~n",
+ "** Reason for termination = ",P,":",P,"~n",
+ "** Callback mode = ",P,"~n",
+ case Q of
+ [_,_|_] -> "** Queued = "++P++"~n";
+ _ -> ""
+ end,
+ case Postponed of
+ [] -> "";
+ _ -> "** Postponed = "++P++"~n"
+ end,
+ case FixedStacktrace of
+ [] -> "";
+ _ -> "** Stacktrace =~n** "++P++"~n"
+ end,
+ case Timeouts of
+ {0,_} -> "";
+ _ -> "** Time-outs: "++P++"~n"
+ end,
+ case Log of
+ [] -> "";
+ _ -> "** Log =~n** "++P++"~n"
+ end]),
+ Args0 =
+ [Name |
case Q of
- [_,_|_] -> "** Queued = ~tp~n";
- _ -> ""
- end ++
- case Postponed of
- [] -> "";
- _ -> "** Postponed = ~tp~n"
- end ++
- case FixedStacktrace of
- [] -> "";
- _ -> "** Stacktrace =~n** ~tp~n"
- end ++
- case Timeouts of
- {0,_} -> "";
- _ -> "** Time-outs: ~p~n"
- end ++
- case Log of
- [] -> "";
- _ -> "** Log =~n** ~tp~n"
- end ++ ClientFmt,
- [Name |
- case Q of
- [] -> [];
- [Event|_] -> [error_logger:limit_term(Event)]
- end] ++
- [error_logger:limit_term(FmtData),
- Class,error_logger:limit_term(FixedReason),
- CBMode] ++
- case Q of
- [_|[_|_] = Events] -> [error_logger:limit_term(Events)];
- _ -> []
- end ++
- case Postponed of
- [] -> [];
- _ -> [error_logger:limit_term(Postponed)]
- end ++
- case FixedStacktrace of
[] -> [];
- _ -> [error_logger:limit_term(FixedStacktrace)]
- end ++
- case Timeouts of
- {0,_} -> [];
- _ -> [error_logger:limit_term(Timeouts)]
- end ++
- case Log of
- [] -> [];
- _ -> [[error_logger:limit_term(T) || T <- Log]]
- end ++ ClientArgs}.
+ [Event|_] -> [Event]
+ end] ++
+ [FmtData,
+ Class,FixedReason,
+ CBMode] ++
+ case Q of
+ [_|[_|_] = Events] -> [Events];
+ _ -> []
+ end ++
+ case Postponed of
+ [] -> [];
+ _ -> [Postponed]
+ end ++
+ case FixedStacktrace of
+ [] -> [];
+ _ -> [FixedStacktrace]
+ end ++
+ case Timeouts of
+ {0,_} -> [];
+ _ -> [Timeouts]
+ end ++
+ case Log of
+ [] -> [];
+ _ -> [Log]
+ end,
+ Args = case Depth of
+ unlimited ->
+ Args0;
+ _ ->
+ lists:flatmap(fun(A) -> [A, Depth] end, Args0)
+ end,
+ {Format++ClientFmt,Args++ClientArgs}.
+
+fix_reason(Class, Reason, Stacktrace) ->
+ case Stacktrace of
+ [{M,F,Args,_}|ST]
+ when Class =:= error, Reason =:= undef ->
+ case code:is_loaded(M) of
+ false ->
+ {{'module could not be loaded',M},ST};
+ _ ->
+ Arity =
+ if
+ is_list(Args) ->
+ length(Args);
+ is_integer(Args) ->
+ Args
+ end,
+ case erlang:function_exported(M, F, Arity) of
+ true ->
+ {Reason,Stacktrace};
+ false ->
+ {{'function not exported',{M,F,Arity}},ST}
+ end
+ end;
+ _ -> {Reason,Stacktrace}
+ end.
-format_client_log(undefined) ->
+format_client_log_single(undefined, _, _) ->
{"", []};
-format_client_log({Pid,dead}) ->
+format_client_log_single({Pid,dead}, _, _) ->
+ {" Client ~0p is dead.", [Pid]};
+format_client_log_single({Pid,remote}, _, _) ->
+ {" Client ~0p is remote on node ~0p.", [Pid,node(Pid)]};
+format_client_log_single({_Pid,{Name,Stacktrace0}}, P, Depth) ->
+ %% Minimize the stacktrace a bit for single line reports. This is
+ %% hopefully enough to point out the position.
+ Stacktrace = lists:sublist(Stacktrace0, 4),
+ Format = lists:append([" Client ",P," stacktrace: ",P,"."]),
+ Args = case Depth of
+ unlimited ->
+ [Name, Stacktrace];
+ _ ->
+ [Name, Depth, Stacktrace, Depth]
+ end,
+ {Format, Args}.
+
+format_client_log(undefined, _, _) ->
+ {"", []};
+format_client_log({Pid,dead}, _, _) ->
{"** Client ~p is dead~n", [Pid]};
-format_client_log({Pid,remote}) ->
- {"** Client ~p is remote on node ~p~n", [Pid, node(Pid)]};
-format_client_log({_Pid,{Name,Stacktrace}}) ->
- {"** Client ~tp stacktrace~n"
- "** ~tp~n",
- [Name, error_logger:limit_term(Stacktrace)]}.
-
+format_client_log({Pid,remote}, _, _) ->
+ {"** Client ~p is remote on node ~p~n", [Pid,node(Pid)]};
+format_client_log({_Pid,{Name,Stacktrace}}, P, Depth) ->
+ Format = lists:append(["** Client ",P," stacktrace~n** ",P,"~n"]),
+ Args = case Depth of
+ unlimited ->
+ [Name, Stacktrace];
+ _ ->
+ [Name, Depth, Stacktrace, Depth]
+ end,
+ {Format,Args}.
+
+p(#{single_line:=Single,depth:=Depth,encoding:=Enc}) ->
+ "~"++single(Single)++mod(Enc)++p(Depth);
+p(unlimited) ->
+ "p";
+p(_Depth) ->
+ "P".
+
+single(true) -> "0";
+single(false) -> "".
+
+mod(latin1) -> "";
+mod(_) -> "t".
%% Call Module:format_status/2 or return a default value
format_status(
diff --git a/lib/stdlib/src/io.erl b/lib/stdlib/src/io.erl
index 63c9a6bddf..1848aa3628 100644
--- a/lib/stdlib/src/io.erl
+++ b/lib/stdlib/src/io.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2018. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2019. 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.
@@ -106,7 +106,6 @@ nl() ->
IoDevice :: device().
nl(Io) ->
-% o_request(Io, {put_chars,io_lib:nl()}).
o_request(Io, nl, nl).
-spec columns() -> {'ok', pos_integer()} | {'error', 'enotsup'}.
@@ -255,8 +254,6 @@ read(Io, Prompt) ->
case request(Io, {get_until,unicode,Prompt,erl_scan,tokens,[1]}) of
{ok,Toks,_EndLine} ->
erl_parse:parse_term(Toks);
-% {error, Reason} when atom(Reason) ->
-% erlang:error(conv_reason(read, Reason), [Io, Prompt]);
{error,E,_EndLine} ->
{error,E};
{eof,_EndLine} ->
@@ -352,12 +349,7 @@ fread(Prompt, Format) ->
| server_no_data().
fread(Io, Prompt, Format) ->
- case request(Io, {fread,Prompt,Format}) of
-% {error, Reason} when atom(Reason) ->
-% erlang:error(conv_reason(fread, Reason), [Io, Prompt, Format]);
- Other ->
- Other
- end.
+ request(Io, {fread,Prompt,Format}).
-spec format(Format) -> 'ok' when
Format :: format().
diff --git a/lib/stdlib/src/io_lib.erl b/lib/stdlib/src/io_lib.erl
index 21d66c5529..e2823b70f2 100644
--- a/lib/stdlib/src/io_lib.erl
+++ b/lib/stdlib/src/io_lib.erl
@@ -78,7 +78,7 @@
%% Utilities for collecting characters.
-export([collect_chars/3, collect_chars/4,
- collect_line/2, collect_line/3, collect_line/4,
+ collect_line/3, collect_line/4,
get_until/3, get_until/4]).
%% The following functions were used by Yecc's include-file.
@@ -851,6 +851,7 @@ collect_chars({binary,Stack,N}, Data,latin1, _) ->
end;
collect_chars({list,Stack,N}, Data, _,_) ->
collect_chars_list(Stack, N, Data);
+
%% collect_chars(Continuation, MoreChars, Count)
%% Returns:
%% {done,Result,RestChars}
@@ -881,32 +882,6 @@ collect_chars_list(Stack, N, []) ->
collect_chars_list(Stack,N, [H|T]) ->
collect_chars_list([H|Stack], N-1, T).
-%% collect_line(Continuation, MoreChars)
-%% Returns:
-%% {done,Result,RestChars}
-%% {more,Continuation}
-%%
-%% XXX Can be removed when compatibility with pre-R12B-5 nodes
-%% is no longer required.
-%%
-collect_line([], Chars) ->
- collect_line1(Chars, []);
-collect_line({SoFar}, More) ->
- collect_line1(More, SoFar).
-
-collect_line1([$\r, $\n|Rest], Stack) ->
- collect_line1([$\n|Rest], Stack);
-collect_line1([$\n|Rest], Stack) ->
- {done,lists:reverse([$\n|Stack], []),Rest};
-collect_line1([C|Rest], Stack) ->
- collect_line1(Rest, [C|Stack]);
-collect_line1(eof, []) ->
- {done,eof,[]};
-collect_line1(eof, Stack) ->
- {done,lists:reverse(Stack, []),[]};
-collect_line1([], Stack) ->
- {more,{Stack}}.
-
%% collect_line(State, Data, _). New in R9C.
%% Returns:
%% {stop,Result,RestData}
diff --git a/lib/stdlib/src/io_lib_pretty.erl b/lib/stdlib/src/io_lib_pretty.erl
index 77f02eafe0..838d412d0c 100644
--- a/lib/stdlib/src/io_lib_pretty.erl
+++ b/lib/stdlib/src/io_lib_pretty.erl
@@ -895,9 +895,6 @@ write_string(S, _Uni) ->
io_lib:write_string(S, $"). %"
expand({_, _, _Dots=0, no_more} = If, _T, _Dd) -> If;
-%% expand({{list,L}, _Len, _, no_more}, T, Dd) ->
-%% {NL, NLen, NDots} = expand_list(L, T, Dd, 2),
-%% {{list,NL}, NLen, NDots, no_more};
expand({{tuple,IsTagged,L}, _Len, _, no_more}, T, Dd) ->
{NL, NLen, NDots} = expand_list(L, T, Dd, 2),
{{tuple,IsTagged,NL}, NLen, NDots, no_more};
diff --git a/lib/stdlib/src/maps.erl b/lib/stdlib/src/maps.erl
index 51965ddb57..49d6a12eb2 100644
--- a/lib/stdlib/src/maps.erl
+++ b/lib/stdlib/src/maps.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2013-2018. All Rights Reserved.
+%% Copyright Ericsson AB 2013-2019. 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.
@@ -100,6 +100,7 @@ merge(_,_) -> erlang:nif_error(undef).
put(_,_,_) -> erlang:nif_error(undef).
+%% Shadowed by erl_bif_types: maps:remove/2
-spec remove(Key,Map1) -> Map2 when
Key :: term(),
Map1 :: map(),
diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl
index fa34f19637..57439c515e 100644
--- a/lib/stdlib/src/otp_internal.erl
+++ b/lib/stdlib/src/otp_internal.erl
@@ -1,574 +1,438 @@
%%
-%% %CopyrightBegin%
+%% WARNING: DO NOT EDIT THIS FILE.
%%
-%% Copyright Ericsson AB 1999-2018. All Rights Reserved.
+%% This file was auto-generated from attributes in the source
+%% code.
%%
-%% Licensed under the Apache License, Version 2.0 (the "License");
-%% you may not use this file except in compliance with the License.
-%% You may obtain a copy of the License at
+%% To add a description to a deprecation or removal attribute,
+%% write a string after the arity:
%%
-%% http://www.apache.org/licenses/LICENSE-2.0
+%% -deprecated([{foo,1,"use bar/1 instead"}]).
+%% -deprecated_type([{gadget,1,"use widget/1 instead"}]).
+%% -removed([{hello,2,"use there/2 instead"}]).
+%% -removed_type([{frobnitz,1,"use grunka/1 instead"}]).
%%
-%% Unless required by applicable law or agreed to in writing, software
-%% distributed under the License is distributed on an "AS IS" BASIS,
-%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-%% See the License for the specific language governing permissions and
-%% limitations under the License.
+%% Descriptions cannot be given with the `f/1` shorthand, and
+%% it will fall back to a generic description referring the
+%% user to the documentation.
%%
-%% %CopyrightEnd%
+%% Use `./otp_build update_deprecations` to update this file
+%% after adding an attribute.
%%
-module(otp_internal).
-
--export([obsolete/3, obsolete_type/3]).
-
-%%----------------------------------------------------------------------
-
+-include("otp_internal.hrl").
+%%
-dialyzer({no_match, obsolete/3}).
-
--type tag() :: 'deprecated' | 'removed'. %% | 'experimental'.
--type mfas() :: mfa() | {atom(), atom(), [byte()]}.
--type release() :: string().
-
--spec obsolete(module(), atom(), arity()) ->
- 'no' | {tag(), string()} | {tag(), mfas(), release()}.
-
-obsolete(Module, Name, Arity) ->
- case obsolete_1(Module, Name, Arity) of
- {deprecated=Tag,{_,_,_}=Replacement} ->
- {Tag,Replacement,"a future release"};
- {_,String}=Ret when is_list(String) ->
- Ret;
- {_,_,_}=Ret ->
- Ret;
- no ->
- no
- end.
-
-obsolete_1(net, call, 4) ->
- {deprecated, {rpc, call, 4}};
-obsolete_1(net, cast, 4) ->
- {deprecated, {rpc, cast, 4}};
-obsolete_1(net, broadcast, 3) ->
- {deprecated, {rpc, eval_everywhere, 3}};
-obsolete_1(net, ping, 1) ->
- {deprecated, {net_adm, ping, 1}};
-obsolete_1(net, sleep, 1) ->
- {deprecated, "Use 'receive after T -> ok end' instead"};
-obsolete_1(net, relay, 1) ->
- {deprecated, {slave, relay, 1}};
-
-
-obsolete_1(erlang, now, 0) ->
- {deprecated,
- "Deprecated BIF. See the \"Time and Time Correction in Erlang\" "
- "chapter of the ERTS User's Guide for more information."};
-
-obsolete_1(calendar, local_time_to_universal_time, 1) ->
- {deprecated, {calendar, local_time_to_universal_time_dst, 1}};
-
-%% *** STDLIB added in OTP 22 ***
-
-obsolete_1(sys, get_debug, 3) ->
- {deprecated,
- "Deprecated function. "
- "Incorrectly documented and in fact only for internal use. "
- "Can often be replaced with sys:get_log/1."};
-
-%% *** STDLIB added in OTP 20 ***
-
-obsolete_1(gen_fsm, start, 3) ->
- {deprecated, {gen_statem, start, 3}};
-obsolete_1(gen_fsm, start, 4) ->
- {deprecated, {gen_statem, start, 4}};
-
-obsolete_1(gen_fsm, start_link, 3) ->
- {deprecated, {gen_statem, start_link, 3}};
-obsolete_1(gen_fsm, start_link, 4) ->
- {deprecated, {gen_statem, start_link, 4}};
-
-obsolete_1(gen_fsm, stop, 1) ->
- {deprecated, {gen_statem, stop, 1}};
-obsolete_1(gen_fsm, stop, 3) ->
- {deprecated, {gen_statem, stop, 3}};
-
-obsolete_1(gen_fsm, enter_loop, 4) ->
- {deprecated, {gen_statem, enter_loop, 4}};
-obsolete_1(gen_fsm, enter_loop, 5) ->
- {deprecated, {gen_statem, enter_loop, 5}};
-obsolete_1(gen_fsm, enter_loop, 6) ->
- {deprecated, {gen_statem, enter_loop, 6}};
-
-obsolete_1(gen_fsm, reply, 2) ->
- {deprecated, {gen_statem, reply, 2}};
-
-obsolete_1(gen_fsm, send_event, 2) ->
- {deprecated, {gen_statem, cast, 2}};
-obsolete_1(gen_fsm, send_all_state_event, 2) ->
- {deprecated, {gen_statem, cast, 2}};
-
-obsolete_1(gen_fsm, sync_send_event, 2) ->
- {deprecated, {gen_statem, call, 2}};
-obsolete_1(gen_fsm, sync_send_event, 3) ->
- {deprecated, {gen_statem, call, 3}};
-
-obsolete_1(gen_fsm, sync_send_all_state_event, 2) ->
- {deprecated, {gen_statem, call, 2}};
-obsolete_1(gen_fsm, sync_send_all_state_event, 3) ->
- {deprecated, {gen_statem, call, 3}};
-
-obsolete_1(gen_fsm, start_timer, 2) ->
- {deprecated, {erlang, start_timer, 3}};
-obsolete_1(gen_fsm, cancel_timer, 1) ->
- {deprecated, {erlang, cancel_timer, 1}};
-obsolete_1(gen_fsm, send_event_after, 2) ->
- {deprecated, {erlang, send_after, 3}};
-
-%% *** CRYPTO added in OTP 20 ***
-
-obsolete_1(crypto, rand_uniform, 2) ->
- {deprecated, {rand, uniform, 1}};
-
-%% *** CRYPTO added in OTP 19 ***
-
-obsolete_1(crypto, rand_bytes, 1) ->
- {removed, {crypto, strong_rand_bytes, 1}, "20.0"};
-
-%% *** CRYPTO added in R16B01 ***
-
-obsolete_1(crypto, md4, 1) ->
- {removed, {crypto, hash, 2}, "20.0"};
-obsolete_1(crypto, md5, 1) ->
- {removed, {crypto, hash, 2}, "20.0"};
-obsolete_1(crypto, sha, 1) ->
- {removed, {crypto, hash, 2}, "20.0"};
-
-obsolete_1(crypto, md4_init, 0) ->
- {removed, {crypto, hash_init, 1}, "20.0"};
-obsolete_1(crypto, md5_init, 0) ->
- {removed, {crypto, hash_init, 1}, "20.0"};
-obsolete_1(crypto, sha_init, 0) ->
- {removed, {crypto, hash_init, 1}, "20.0"};
-
-obsolete_1(crypto, md4_update, 2) ->
- {removed, {crypto, hash_update, 2}, "20.0"};
-obsolete_1(crypto, md5_update, 2) ->
- {removed, {crypto, hash_update, 2}, "20.0"};
-obsolete_1(crypto, sha_update, 2) ->
- {removed, {crypto, hash_update, 2}, "20.0"};
-
-obsolete_1(crypto, md4_final, 1) ->
- {removed, {crypto, hash_final, 1}, "20.0"};
-obsolete_1(crypto, md5_final, 1) ->
- {removed, {crypto, hash_final, 1}, "20.0"};
-obsolete_1(crypto, sha_final, 1) ->
- {removed, {crypto, hash_final, 1}, "20.0"};
-
-obsolete_1(crypto, md5_mac, 2) ->
- {removed, {crypto, hmac, 3}, "20.0"};
-obsolete_1(crypto, sha_mac, 2) ->
- {removed, {crypto, hmac, 3}, "20.0"};
-obsolete_1(crypto, sha_mac, 3) ->
- {removed, {crypto, hmac, 4}, "20.0"};
-
-obsolete_1(crypto, sha_mac_96, 2) ->
- {removed, {crypto, hmac, 4}, "20.0"};
-obsolete_1(crypto, md5_mac_96, 2) ->
- {removed, {crypto, hmac, 4}, "20.0"};
-
-obsolete_1(crypto, rsa_sign, 2) ->
- {removed, {crypto, sign, 4}, "20.0"};
-obsolete_1(crypto, rsa_sign, 3) ->
- {removed, {crypto, sign, 4}, "20.0"};
-obsolete_1(crypto, rsa_verify, 3) ->
- {removed, {crypto, verify, 5}, "20.0"};
-obsolete_1(crypto, rsa_verify, 4) ->
- {removed, {crypto, verify, 5}, "20.0"};
-
-obsolete_1(crypto, dss_sign, 2) ->
- {removed, {crypto, sign, 4}, "20.0"};
-obsolete_1(crypto, dss_sign, 3) ->
- {removed, {crypto, sign, 4}, "20.0"};
-
-obsolete_1(crypto, dss_verify, 3) ->
- {removed, {crypto, verify, 5}, "20.0"};
-obsolete_1(crypto, dss_verify, 4) ->
- {removed, {crypto, verify, 5}, "20.0"};
-
-obsolete_1(crypto, mod_exp, 3) ->
- {removed, {crypto, mod_pow, 3}, "20.0"};
-
-obsolete_1(crypto, dh_compute_key, 3) ->
- {removed, {crypto, compute_key, 4}, "20.0"};
-obsolete_1(crypto, dh_generate_key, 1) ->
- {removed, {crypto, generate_key, 2}, "20.0"};
-obsolete_1(crypto, dh_generate_key, 2) ->
- {removed, {crypto, generate_key, 3}, "20.0"};
-
-obsolete_1(crypto, des_cbc_encrypt, 3) ->
- {removed, {crypto, block_encrypt, 4}, "20.0"};
-obsolete_1(crypto, des3_cbc_encrypt, 5) ->
- {removed, {crypto, block_encrypt, 4}, "20.0"};
-obsolete_1(crypto, des_ecb_encrypt, 2) ->
- {removed, {crypto, block_encrypt, 3}, "20.0"};
-obsolete_1(crypto, des_ede3_cbc_encrypt, 5) ->
- {removed, {crypto, block_encrypt, 4}, "20.0"};
-obsolete_1(crypto, des_cfb_encrypt, 3) ->
- {removed, {crypto, block_encrypt, 4}, "20.0"};
-obsolete_1(crypto, des3_cfb_encrypt, 5) ->
- {removed, {crypto, block_encrypt, 4}, "20.0"};
-obsolete_1(crypto, blowfish_ecb_encrypt, 2) ->
- {removed, {crypto, block_encrypt, 3}, "20.0"};
-obsolete_1(crypto, blowfish_cbc_encrypt, 3) ->
- {removed, {crypto, block_encrypt, 4}, "20.0"};
-obsolete_1(crypto, blowfish_cfb64_encrypt, 3) ->
- {removed, {crypto, block_encrypt, 4}, "20.0"};
-obsolete_1(crypto, blowfish_ofb64_encrypt, 3) ->
- {removed, {crypto, block_encrypt, 4}, "20.0"};
-obsolete_1(crypto, aes_cfb_128_encrypt, 3) ->
- {removed, {crypto, block_encrypt, 4}, "20.0"};
-obsolete_1(crypto, aes_cbc_128_encrypt, 3) ->
- {removed, {crypto, block_encrypt, 4}, "20.0"};
-obsolete_1(crypto, aes_cbc_256_encrypt, 3) ->
- {removed, {crypto, block_encrypt, 4}, "20.0"};
-obsolete_1(crypto,rc2_cbc_encrypt, 3) ->
- {removed, {crypto, block_encrypt, 4}, "20.0"};
-obsolete_1(crypto,rc2_40_cbc_encrypt, 3) ->
- {removed, {crypto, block_encrypt, 4}, "20.0"};
-
-obsolete_1(crypto, des_cbc_decrypt, 3) ->
- {removed, {crypto, block_decrypt, 4}, "20.0"};
-obsolete_1(crypto, des3_cbc_decrypt, 5) ->
- {removed, {crypto, block_decrypt, 4}, "20.0"};
-obsolete_1(crypto, des_ecb_decrypt, 2) ->
- {removed, {crypto, block_decrypt, 3}, "20.0"};
-obsolete_1(crypto, des_ede3_cbc_decrypt, 5) ->
- {removed, {crypto, block_decrypt, 4}, "20.0"};
-obsolete_1(crypto, des_cfb_decrypt, 3) ->
- {removed, {crypto, block_decrypt, 4}, "20.0"};
-obsolete_1(crypto, des3_cfb_decrypt, 5) ->
- {removed, {crypto, block_decrypt, 4}, "20.0"};
-obsolete_1(crypto, blowfish_ecb_decrypt, 2) ->
- {removed, {crypto, block_decrypt, 3}, "20.0"};
-obsolete_1(crypto, blowfish_cbc_decrypt, 3) ->
- {removed, {crypto, block_decrypt, 4}, "20.0"};
-obsolete_1(crypto, blowfish_cfb64_decrypt, 3) ->
- {removed, {crypto, block_decrypt, 4}, "20.0"};
-obsolete_1(crypto, blowfish_ofb64_decrypt, 3) ->
- {removed, {crypto, block_decrypt, 4}, "20.0"};
-obsolete_1(crypto, aes_cfb_128_decrypt, 3) ->
- {removed, {crypto, block_decrypt, 4}, "20.0"};
-obsolete_1(crypto, aes_cbc_128_decrypt, 3) ->
- {removed, {crypto, block_decrypt, 4}, "20.0"};
-obsolete_1(crypto, aes_cbc_256_decrypt, 3) ->
- {removed, {crypto, block_decrypt, 4}, "20.0"};
-obsolete_1(crypto,rc2_cbc_decrypt, 3) ->
- {removed, {crypto, block_decrypt, 4}, "20.0"};
-obsolete_1(crypto,rc2_40_cbc_decrypt, 3) ->
- {removed, {crypto, block_decrypt, 4}, "20.0"};
-
-obsolete_1(crypto, aes_ctr_stream_decrypt, 2) ->
- {removed, {crypto, stream_decrypt, 2}, "20.0"};
-obsolete_1(crypto, aes_ctr_stream_encrypt, 2) ->
- {removed, {crypto, stream_encrypt, 2}, "20.0"};
-obsolete_1(crypto, aes_ctr_decrypt, 3) ->
- {removed, {crypto, stream_decrypt, 2}, "20.0"};
-obsolete_1(crypto, aes_ctr_encrypt, 3) ->
- {removed, {crypto, stream_encrypt, 2}, "20.0"};
-obsolete_1(crypto, rc4_encrypt, 2) ->
- {removed, {crypto, stream_encrypt, 2}, "20.0"};
-obsolete_1(crypto, rc4_encrypt_with_state, 2) ->
- {removed, {crypto, stream_encrypt, 2}, "20.0"};
-obsolete_1(crypto, aes_ctr_stream_init, 2) ->
- {removed, {crypto, stream_init, 3}, "20.0"};
-obsolete_1(crypto, rc4_set_key, 1) ->
- {removed, {crypto, stream_init, 2}, "20.0"};
-
-obsolete_1(crypto, rsa_private_decrypt, 3) ->
- {removed, {crypto, private_decrypt, 4}, "20.0"};
-obsolete_1(crypto, rsa_public_decrypt, 3) ->
- {removed, {crypto, public_decrypt, 4}, "20.0"};
-obsolete_1(crypto, rsa_private_encrypt, 3) ->
- {removed, {crypto, private_encrypt, 4}, "20.0"};
-obsolete_1(crypto, rsa_public_encrypt, 3) ->
- {removed, {crypto, public_encrypt, 4}, "20.0"};
-
-obsolete_1(crypto, des_cfb_ivec, 2) ->
- {removed, {crypto, next_iv, 3}, "20.0"};
-obsolete_1(crypto,des_cbc_ivec, 1) ->
- {removed, {crypto, next_iv, 2}, "20.0"};
-obsolete_1(crypto, aes_cbc_ivec, 1) ->
- {removed, {crypto, next_iv, 2}, "20.0"};
-
-obsolete_1(crypto,info, 0) ->
- {removed, {crypto, module_info, 0}, "20.0"};
-
-obsolete_1(crypto, strong_rand_mpint, 3) ->
- {removed, "removed in 20.0; only needed by removed functions"};
-obsolete_1(crypto, erlint, 1) ->
- {removed, "removed in 20.0; only needed by removed functions"};
-obsolete_1(crypto, mpint, 1) ->
- {removed, "removed in 20.0; only needed by removed functions"};
-
-
-%% *** SNMP ***
-
-obsolete_1(snmp, N, A) ->
- case is_snmp_agent_function(N, A) of
- false ->
- no;
- true ->
- {deprecated, "Deprecated (will be removed in OTP 18); use snmpa:"++atom_to_list(N)++"/"++
- integer_to_list(A)++" instead"}
- end;
-
-obsolete_1(snmpa, old_info_format, 1) ->
- {deprecated, "Deprecated; (will be removed in OTP 18); use \"new\" format instead"};
-
-
-%% *** MEGACO ***
-
-obsolete_1(megaco, format_versions, 1) ->
- {deprecated, "Deprecated; use megaco:print_version_info/0,1 instead"};
-
-
-%% *** OS-MON-MIB ***
-
-%% FIXME: Remove this warning in OTP 24.
-obsolete_1(os_mon_mib, _, _) ->
- {removed, "was removed in 22.0"};
-
-obsolete_1(auth, is_auth, 1) ->
- {deprecated, {net_adm, ping, 1}};
-obsolete_1(auth, cookie, 0) ->
- {deprecated, {erlang, get_cookie, 0}};
-obsolete_1(auth, cookie, 1) ->
- {deprecated, {erlang, set_cookie, 2}};
-obsolete_1(auth, node_cookie, 1) ->
- {deprecated, "Deprecated; use erlang:set_cookie/2 and net_adm:ping/1 instead"};
-obsolete_1(auth, node_cookie, 2) ->
- {deprecated, "Deprecated; use erlang:set_cookie/2 and net_adm:ping/1 instead"};
-
-%% Added in R16
-obsolete_1(wxCalendarCtrl, enableYearChange, _) -> %% wx bug documented?
- {deprecated,"deprecated function not available in wxWidgets-2.9 and later"};
-obsolete_1(wxDC, computeScaleAndOrigin, 1) ->
- {deprecated,"deprecated function not available in wxWidgets-2.9 and later"};
-obsolete_1(wxClientDC, new, 0) ->
- {deprecated,"deprecated function not available in wxWidgets-2.9 and later"};
-obsolete_1(wxPaintDC, new, 0) ->
- {deprecated,"deprecated function not available in wxWidgets-2.9 and later"};
-obsolete_1(wxWindowDC, new, 0) ->
- {deprecated,"deprecated function not available in wxWidgets-2.9 and later"};
-obsolete_1(wxGraphicsRenderer, createLinearGradientBrush, 7) ->
- {deprecated,"deprecated function not available in wxWidgets-2.9 and later"};
-obsolete_1(wxGraphicsRenderer, createRadialGradientBrush, 8) ->
- {deprecated,"deprecated function not available in wxWidgets-2.9 and later"};
-obsolete_1(wxGridCellEditor, endEdit, 4) ->
- {deprecated,"deprecated function not available in wxWidgets-2.9 and later"};
-obsolete_1(wxGridCellEditor, paintBackground, 3) ->
- {deprecated,"deprecated function not available in wxWidgets-2.9 and later"};
-obsolete_1(wxIdleEvent, canSend, 1) ->
- {deprecated,"deprecated function not available in wxWidgets-2.9 and later"};
-obsolete_1(wxMDIClientWindow, new, 1) ->
- {deprecated,"deprecated function not available in wxWidgets-2.9 and later"};
-obsolete_1(wxMDIClientWindow, new, 2) ->
- {deprecated,"deprecated function not available in wxWidgets-2.9 and later"};
-obsolete_1(wxPostScriptDC, getResolution, 0) ->
- {deprecated,"deprecated function not available in wxWidgets-2.9 and later"};
-obsolete_1(wxPostScriptDC, setResolution, 1) ->
- {deprecated,"deprecated function not available in wxWidgets-2.9 and later"};
-obsolete_1(wxCursor, new, 3) ->
- {deprecated,"deprecated function not available in wxWidgets-2.9 and later"};
-obsolete_1(wxCursor, new, 4) ->
- {deprecated,"deprecated function not available in wxWidgets-2.9 and later"};
-
-%% Added in OTP 17.
-obsolete_1(asn1ct, decode,3) ->
- {removed,"removed; use Mod:decode/2 instead"};
-obsolete_1(asn1ct, encode, 2) ->
- {removed,"removed; use Mod:encode/2 instead"};
-obsolete_1(asn1ct, encode, 3) ->
- {removed,"removed; use Mod:encode/2 instead"};
-obsolete_1(asn1rt, decode,3) ->
- {removed,"removed; use Mod:decode/2 instead"};
-obsolete_1(asn1rt, encode, 2) ->
- {removed,"removed; use Mod:encode/2 instead"};
-obsolete_1(asn1rt, encode, 3) ->
- {removed,"removed; use Mod:encode/2 instead"};
-obsolete_1(asn1rt, info, 1) ->
- {removed,"removed; use Mod:info/0 instead"};
-obsolete_1(asn1rt, utf8_binary_to_list, 1) ->
- {removed,{unicode,characters_to_list,1},"OTP 20"};
-obsolete_1(asn1rt, utf8_list_to_binary, 1) ->
- {removed,{unicode,characters_to_binary,1},"OTP 20"};
-
-%% Added in OTP 18.
-obsolete_1(core_lib, get_anno, 1) ->
- {removed,{cerl,get_ann,1},"19"};
-obsolete_1(core_lib, set_anno, 2) ->
- {removed,{cerl,set_ann,2},"19"};
-obsolete_1(core_lib, is_literal, 1) ->
- {removed,{cerl,is_literal,1},"19"};
-obsolete_1(core_lib, is_literal_list, 1) ->
- {removed,"removed; use lists:all(fun cerl:is_literal/1, L)"
- " instead"};
-obsolete_1(core_lib, literal_value, 1) ->
- {removed,{core_lib,concrete,1},"19"};
-obsolete_1(erl_scan, set_attribute, 3) ->
- {removed,{erl_anno,set_line,2},"19.0"};
-obsolete_1(erl_scan, attributes_info, 1) ->
- {removed,"removed in 19.0; use "
- "erl_anno:{column,line,location,text}/1 instead"};
-obsolete_1(erl_scan, attributes_info, 2) ->
- {removed,"removed in 19.0; use "
- "erl_anno:{column,line,location,text}/1 instead"};
-obsolete_1(erl_scan, token_info, 1) ->
- {removed,"removed in 19.0; use "
- "erl_scan:{category,column,line,location,symbol,text}/1 instead"};
-obsolete_1(erl_scan, token_info, 2) ->
- {removed,"removed in 19.0; use "
- "erl_scan:{category,column,line,location,symbol,text}/1 instead"};
-obsolete_1(erl_parse, set_line, 2) ->
- {removed,{erl_anno,set_line,2},"19.0"};
-obsolete_1(erl_parse, get_attributes, 1) ->
- {removed,"removed in 19.0; use "
- "erl_anno:{column,line,location,text}/1 instead"};
-obsolete_1(erl_parse, get_attribute, 2) ->
- {removed,"removed in 19.0; use "
- "erl_anno:{column,line,location,text}/1 instead"};
-obsolete_1(erl_lint, modify_line, 2) ->
- {removed,{erl_parse,map_anno,2},"19.0"};
-obsolete_1(ssl, negotiated_next_protocol, 1) ->
- {removed,"removed in 20.0; use ssl:negotiated_protocol/1 instead"};
-obsolete_1(ssl, connection_info, 1) ->
- {removed, "removed in 20.0; use ssl:connection_information/[1,2] instead"};
-
-obsolete_1(httpd_conf, check_enum, 2) ->
- {deprecated, "deprecated; use lists:member/2 instead"};
-obsolete_1(httpd_conf, clean, 1) ->
- {deprecated, "deprecated; use sting:strip/1 instead or possible the re module"};
-obsolete_1(httpd_conf, custom_clean, 3) ->
- {deprecated, "deprecated; use sting:strip/3 instead or possible the re module"};
-obsolete_1(httpd_conf, is_directory, 1) ->
- {deprecated, "deprecated; use filelib:is_dir/1 instead"};
-obsolete_1(httpd_conf, is_file, 1) ->
- {deprecated, "deprecated; use filelib:is_file/1 instead"};
-obsolete_1(httpd_conf, make_integer, 1) ->
- {deprecated, "deprecated; use erlang:list_to_integer/1 instead"};
-
-%% Added in OTP 19.
-
-obsolete_1(random, _, _) ->
- {deprecated, "the 'random' module is deprecated; "
- "use the 'rand' module instead"};
-obsolete_1(code, rehash, 0) ->
- {deprecated, "deprecated because the code path cache feature has been removed"};
-obsolete_1(queue, lait, 1) ->
- {deprecated, {queue,liat,1}};
-
-%% Removed in OTP 19.
-
-obsolete_1(rpc, safe_multi_server_call, A) when A =:= 2; A =:= 3 ->
- {removed, {rpc, multi_server_call, A}, "19.0"};
-
-%% Added in OTP 20.
-
-obsolete_1(filename, find_src, 1) ->
- {deprecated, "deprecated; use filelib:find_source/1 instead"};
-obsolete_1(filename, find_src, 2) ->
- {deprecated, "deprecated; use filelib:find_source/3 instead"};
-
-obsolete_1(erlang, get_stacktrace, 0) ->
- {deprecated, "deprecated; use the new try/catch syntax for retrieving the stack backtrace"};
-
-%% Removed in OTP 20.
-
-obsolete_1(erlang, hash, 2) ->
- {removed, {erlang, phash2, 2}, "20.0"};
-
-%% Add in OTP 21.
-
-obsolete_1(ssl, ssl_accept, 1) ->
- {deprecated, "deprecated; use ssl:handshake/1 instead"};
-obsolete_1(ssl, ssl_accept, 2) ->
- {deprecated, "deprecated; use ssl:handshake/2 instead"};
-obsolete_1(ssl, ssl_accept, 3) ->
- {deprecated, "deprecated; use ssl:handshake/3 instead"};
-obsolete_1(otp_mib, F, _) when F =:= load; F =:= unload ->
- {deprecated, "deprecated; functionality will be removed in a future release"};
-
-%% not obsolete
-
-obsolete_1(_, _, _) ->
- no.
-
--spec is_snmp_agent_function(atom(), byte()) -> boolean().
-
-is_snmp_agent_function(c, 1) -> true;
-is_snmp_agent_function(c, 2) -> true;
-is_snmp_agent_function(compile, 3) -> true;
-is_snmp_agent_function(is_consistent, 1) -> true;
-is_snmp_agent_function(mib_to_hrl, 1) -> true;
-is_snmp_agent_function(change_log_size, 1) -> true;
-is_snmp_agent_function(log_to_txt, 2) -> true;
-is_snmp_agent_function(log_to_txt, 3) -> true;
-is_snmp_agent_function(log_to_txt, 4) -> true;
-is_snmp_agent_function(current_request_id, 0) -> true;
-is_snmp_agent_function(current_community, 0) -> true;
-is_snmp_agent_function(current_address, 0) -> true;
-is_snmp_agent_function(current_context, 0) -> true;
-is_snmp_agent_function(current_net_if_data, 0) -> true;
-is_snmp_agent_function(get_symbolic_store_db, 0) -> true;
-is_snmp_agent_function(name_to_oid, 1) -> true;
-is_snmp_agent_function(name_to_oid, 2) -> true;
-is_snmp_agent_function(oid_to_name, 1) -> true;
-is_snmp_agent_function(oid_to_name, 2) -> true;
-is_snmp_agent_function(int_to_enum, 2) -> true;
-is_snmp_agent_function(int_to_enum, 3) -> true;
-is_snmp_agent_function(enum_to_int, 2) -> true;
-is_snmp_agent_function(enum_to_int, 3) -> true;
-is_snmp_agent_function(get, 2) -> true;
-is_snmp_agent_function(info, 1) -> true;
-is_snmp_agent_function(load_mibs, 2) -> true;
-is_snmp_agent_function(unload_mibs, 2) -> true;
-is_snmp_agent_function(dump_mibs, 0) -> true;
-is_snmp_agent_function(dump_mibs, 1) -> true;
-is_snmp_agent_function(register_subagent, 3) -> true;
-is_snmp_agent_function(unregister_subagent, 2) -> true;
-is_snmp_agent_function(send_notification, 3) -> true;
-is_snmp_agent_function(send_notification, 4) -> true;
-is_snmp_agent_function(send_notification, 5) -> true;
-is_snmp_agent_function(send_notification, 6) -> true;
-is_snmp_agent_function(send_trap, 3) -> true;
-is_snmp_agent_function(send_trap, 4) -> true;
-is_snmp_agent_function(add_agent_caps, 2) -> true;
-is_snmp_agent_function(del_agent_caps, 1) -> true;
-is_snmp_agent_function(get_agent_caps, 0) -> true;
-is_snmp_agent_function(_, _) -> false.
-
--dialyzer({no_match, obsolete_type/3}).
-
--spec obsolete_type(module(), atom(), arity()) ->
- 'no' | {tag(), string()} | {tag(), mfas(), release()}.
+obsolete(auth, cookie, 0) ->
+ {deprecated, "use erlang:get_cookie/0 instead"};
+obsolete(auth, cookie, 1) ->
+ {deprecated, "use erlang:set_cookie/2 instead"};
+obsolete(auth, is_auth, 1) ->
+ {deprecated, "use net_adm:ping/1 instead"};
+obsolete(calendar, local_time_to_universal_time, 1) ->
+ {deprecated, "use calendar:local_time_to_universal_time_dst/1 instead"};
+obsolete(code, rehash, 0) ->
+ {deprecated, "the code path cache feature has been removed"};
+obsolete(crypto, block_decrypt, 3) ->
+ {deprecated, "use crypto:crypto_one_time/4 or crypto:crypto_init/3 + crypto:crypto_update/2 + crypto:crypto_final/1 instead"};
+obsolete(crypto, block_decrypt, 4) ->
+ {deprecated, "use crypto:crypto_one_time/5, crypto:crypto_one_time_aead/6,7 or crypto:crypto_(dyn_iv)?_init + crypto:crypto_(dyn_iv)?_update + crypto:crypto_final instead"};
+obsolete(crypto, block_encrypt, 3) ->
+ {deprecated, "use crypto:crypto_one_time/4 or crypto:crypto_init/3 + crypto:crypto_update/2 + crypto:crypto_final/1 instead"};
+obsolete(crypto, block_encrypt, 4) ->
+ {deprecated, "use crypto:crypto_one_time/5, crypto:crypto_one_time_aead/6,7 or crypto:crypto_(dyn_iv)?_init + crypto:crypto_(dyn_iv)?_update + crypto:crypto_final instead"};
+obsolete(crypto, cmac, 3) ->
+ {deprecated, "use crypto:mac/4 instead"};
+obsolete(crypto, cmac, 4) ->
+ {deprecated, "use crypto:macN/5 instead"};
+obsolete(crypto, hmac, 3) ->
+ {deprecated, "use crypto:mac/4 instead"};
+obsolete(crypto, hmac, 4) ->
+ {deprecated, "use crypto:macN/5 instead"};
+obsolete(crypto, hmac_final, 1) ->
+ {deprecated, "use crypto:mac_final/1 instead"};
+obsolete(crypto, hmac_final_n, 2) ->
+ {deprecated, "use crypto:mac_finalN/2 instead"};
+obsolete(crypto, hmac_init, 2) ->
+ {deprecated, "use crypto:mac_init/3 instead"};
+obsolete(crypto, hmac_update, 2) ->
+ {deprecated, "use crypto:mac_update/2 instead"};
+obsolete(crypto, poly1305, 2) ->
+ {deprecated, "use crypto:mac/3 instead"};
+obsolete(crypto, rand_uniform, 2) ->
+ {deprecated, "use rand:rand_uniform/1 instead"};
+obsolete(crypto, stream_decrypt, 2) ->
+ {deprecated, "use crypto:crypto_update/2 instead"};
+obsolete(crypto, stream_encrypt, 2) ->
+ {deprecated, "use crypto:crypto_update/2 instead"};
+obsolete(erlang, get_stacktrace, 0) ->
+ {deprecated, "use the new try/catch syntax for retrieving the stack backtrace"};
+obsolete(erlang, now, 0) ->
+ {deprecated, "see the \"Time and Time Correction in Erlang\" chapter of the ERTS User's Guide for more information"};
+obsolete(filename, safe_relative_path, 1) ->
+ {deprecated, "use filelib:safe_relative_path/2 instead"};
+obsolete(http_uri, decode, 1) ->
+ {deprecated, "use uri_string functions instead"};
+obsolete(http_uri, encode, 1) ->
+ {deprecated, "use uri_string functions instead"};
+obsolete(http_uri, parse, 1) ->
+ {deprecated, "use uri_string functions instead"};
+obsolete(http_uri, parse, 2) ->
+ {deprecated, "use uri_string functions instead"};
+obsolete(http_uri, scheme_defaults, 0) ->
+ {deprecated, "use uri_string functions instead"};
+obsolete(httpd, parse_query, 1) ->
+ {deprecated, "use uri_string:dissect_query/1 instead"};
+obsolete(megaco, format_versions, 1) ->
+ {deprecated, "use megaco:print_version_info/0,1 instead"};
+obsolete(net, broadcast, 3) ->
+ {deprecated, "use rpc:eval_everywhere/3 instead"};
+obsolete(net, call, 4) ->
+ {deprecated, "use rpc:call/4 instead"};
+obsolete(net, cast, 4) ->
+ {deprecated, "use rpc:cast/4 instead"};
+obsolete(net, ping, 1) ->
+ {deprecated, "use net_adm:ping/1 instead"};
+obsolete(net, relay, 1) ->
+ {deprecated, "use slave:relay/1 instead"};
+obsolete(net, sleep, 1) ->
+ {deprecated, "use 'receive after T -> ok end' instead"};
+obsolete(queue, lait, 1) ->
+ {deprecated, "use queue:liat/1 instead"};
+obsolete(snmp, add_agent_caps, 2) ->
+ {deprecated, "use snmpa:add_agent_caps/2 instead"};
+obsolete(snmp, c, 1) ->
+ {deprecated, "use snmpa:c/1 instead"};
+obsolete(snmp, c, 2) ->
+ {deprecated, "use snmpa:c/2 instead"};
+obsolete(snmp, change_log_size, 1) ->
+ {deprecated, "use snmpa:change_log_size/1 instead"};
+obsolete(snmp, compile, 3) ->
+ {deprecated, "use snmpa:compile/3 instead"};
+obsolete(snmp, current_address, 0) ->
+ {deprecated, "use snmpa:current_address/0 instead"};
+obsolete(snmp, current_community, 0) ->
+ {deprecated, "use snmpa:current_community/0 instead"};
+obsolete(snmp, current_context, 0) ->
+ {deprecated, "use snmpa:current_context/0 instead"};
+obsolete(snmp, current_net_if_data, 0) ->
+ {deprecated, "use snmpa:current_net_if_data/0 instead"};
+obsolete(snmp, current_request_id, 0) ->
+ {deprecated, "use snmpa:current_request_id/0 instead"};
+obsolete(snmp, del_agent_caps, 1) ->
+ {deprecated, "use snmpa:del_agent_caps/1 instead"};
+obsolete(snmp, dump_mibs, 0) ->
+ {deprecated, "use snmpa:dump_mibs/0 instead"};
+obsolete(snmp, dump_mibs, 1) ->
+ {deprecated, "use snmpa:dump_mibs/1 instead"};
+obsolete(snmp, enum_to_int, 2) ->
+ {deprecated, "use snmpa:enum_to_int/2 instead"};
+obsolete(snmp, enum_to_int, 3) ->
+ {deprecated, "use snmpa:enum_to_int/3 instead"};
+obsolete(snmp, get, 2) ->
+ {deprecated, "use snmpa:get/2 instead"};
+obsolete(snmp, get_agent_caps, 0) ->
+ {deprecated, "use snmpa:get_agent_caps/0 instead"};
+obsolete(snmp, get_symbolic_store_db, 0) ->
+ {deprecated, "use snmpa:get_symbolic_store_db/0 instead"};
+obsolete(snmp, info, 1) ->
+ {deprecated, "use snmpa:info/1 instead"};
+obsolete(snmp, int_to_enum, 2) ->
+ {deprecated, "use snmpa:int_to_enum/2 instead"};
+obsolete(snmp, int_to_enum, 3) ->
+ {deprecated, "use snmpa:int_to_enum/3 instead"};
+obsolete(snmp, is_consistent, 1) ->
+ {deprecated, "use snmpa:is_consistent/1 instead"};
+obsolete(snmp, load_mibs, 2) ->
+ {deprecated, "use snmpa:load_mibs/2 instead"};
+obsolete(snmp, log_to_txt, 2) ->
+ {deprecated, "use snmpa:log_to_txt/2 instead"};
+obsolete(snmp, log_to_txt, 3) ->
+ {deprecated, "use snmpa:log_to_txt/3 instead"};
+obsolete(snmp, log_to_txt, 4) ->
+ {deprecated, "use snmpa:log_to_txt/4 instead"};
+obsolete(snmp, mib_to_hrl, 1) ->
+ {deprecated, "use snmpa:mib_to_hrl/1 instead"};
+obsolete(snmp, name_to_oid, 1) ->
+ {deprecated, "use snmpa:name_to_oid/1 instead"};
+obsolete(snmp, name_to_oid, 2) ->
+ {deprecated, "use snmpa:name_to_oid/2 instead"};
+obsolete(snmp, oid_to_name, 1) ->
+ {deprecated, "use snmpa:oid_to_name/1 instead"};
+obsolete(snmp, oid_to_name, 2) ->
+ {deprecated, "use snmpa:oid_to_name/2 instead"};
+obsolete(snmp, register_subagent, 3) ->
+ {deprecated, "use snmpa:register_subagent/3 instead"};
+obsolete(snmp, send_notification, 3) ->
+ {deprecated, "use snmpa:send_notification/3 instead"};
+obsolete(snmp, send_notification, 4) ->
+ {deprecated, "use snmpa:send_notification/4 instead"};
+obsolete(snmp, send_notification, 5) ->
+ {deprecated, "use snmpa:send_notification/5 instead"};
+obsolete(snmp, send_notification, 6) ->
+ {deprecated, "use snmpa:send_notification/6 instead"};
+obsolete(snmp, send_trap, 3) ->
+ {deprecated, "use snmpa:send_trap/3 instead"};
+obsolete(snmp, send_trap, 4) ->
+ {deprecated, "use snmpa:send_trap/4 instead"};
+obsolete(snmp, unload_mibs, 2) ->
+ {deprecated, "use snmpa:unload_mibs/2 instead"};
+obsolete(snmp, unregister_subagent, 2) ->
+ {deprecated, "use snmpa:unregister_subagent/2 instead"};
+obsolete(snmpa, old_info_format, 1) ->
+ {deprecated, "use \"new\" format instead"};
+obsolete(sys, get_debug, 3) ->
+ {deprecated, "incorrectly documented and only for internal use. Can often be replaced with sys:get_log/1"};
+obsolete(wxClientDC, new, 0) ->
+ {deprecated, "not available in wxWidgets-2.9 and later"};
+obsolete(wxCursor, new, 3) ->
+ {deprecated, "not available in wxWidgets-2.9 and later"};
+obsolete(wxCursor, new, 4) ->
+ {deprecated, "not available in wxWidgets-2.9 and later"};
+obsolete(wxDC, computeScaleAndOrigin, 1) ->
+ {deprecated, "not available in wxWidgets-2.9 and later"};
+obsolete(wxGraphicsRenderer, createLinearGradientBrush, 7) ->
+ {deprecated, "not available in wxWidgets-2.9 and later"};
+obsolete(wxGraphicsRenderer, createRadialGradientBrush, 8) ->
+ {deprecated, "not available in wxWidgets-2.9 and later"};
+obsolete(wxGridCellEditor, endEdit, 4) ->
+ {deprecated, "not available in wxWidgets-2.9 and later"};
+obsolete(wxGridCellEditor, paintBackground, 3) ->
+ {deprecated, "not available in wxWidgets-2.9 and later"};
+obsolete(wxIdleEvent, canSend, 1) ->
+ {deprecated, "not available in wxWidgets-2.9 and later"};
+obsolete(wxMDIClientWindow, new, 1) ->
+ {deprecated, "not available in wxWidgets-2.9 and later"};
+obsolete(wxMDIClientWindow, new, 2) ->
+ {deprecated, "not available in wxWidgets-2.9 and later"};
+obsolete(wxPaintDC, new, 0) ->
+ {deprecated, "not available in wxWidgets-2.9 and later"};
+obsolete(wxPostScriptDC, getResolution, 0) ->
+ {deprecated, "not available in wxWidgets-2.9 and later"};
+obsolete(wxPostScriptDC, setResolution, 1) ->
+ {deprecated, "not available in wxWidgets-2.9 and later"};
+obsolete(wxWindowDC, new, 0) ->
+ {deprecated, "not available in wxWidgets-2.9 and later"};
+obsolete(core_lib, get_anno, 1) ->
+ {removed, "use cerl:get_ann/1 instead"};
+obsolete(core_lib, is_literal, 1) ->
+ {removed, "use cerl:is_literal/1 instead"};
+obsolete(core_lib, is_literal_list, 1) ->
+ {removed, "use cerl:is_literal_list/1 instead"};
+obsolete(core_lib, literal_value, 1) ->
+ {removed, "use cerl:concrete/1 instead"};
+obsolete(core_lib, set_anno, 2) ->
+ {removed, "use cerl:set_ann/2 instead"};
+obsolete(crypto, aes_cbc_128_decrypt, 3) ->
+ {removed, "use crypto:block_decrypt/4 instead"};
+obsolete(crypto, aes_cbc_128_encrypt, 3) ->
+ {removed, "use crypto:block_encrypt/4 instead"};
+obsolete(crypto, aes_cbc_256_decrypt, 3) ->
+ {removed, "use crypto:block_decrypt/4 instead"};
+obsolete(crypto, aes_cbc_256_encrypt, 3) ->
+ {removed, "use crypto:block_encrypt/4 instead"};
+obsolete(crypto, aes_cbc_ivec, 2) ->
+ {removed, "use crypto:next_iv/2 instead"};
+obsolete(crypto, aes_cfb_128_decrypt, 3) ->
+ {removed, "use crypto:block_decrypt/4 instead"};
+obsolete(crypto, aes_cfb_128_encrypt, 3) ->
+ {removed, "use crypto:block_encrypt/4 instead"};
+obsolete(crypto, aes_ctr_decrypt, 3) ->
+ {removed, "use crypto:stream_decrypt/2 instead"};
+obsolete(crypto, aes_ctr_encrypt, 3) ->
+ {removed, "use crypto:stream_encrypt/2 instead"};
+obsolete(crypto, aes_ctr_stream_decrypt, 2) ->
+ {removed, "use crypto:stream_decrypt/2 instead"};
+obsolete(crypto, aes_ctr_stream_encrypt, 2) ->
+ {removed, "use crypto:stream_encrypt/2 instead"};
+obsolete(crypto, aes_ctr_stream_init, 2) ->
+ {removed, "use crypto:stream_init/3 instead"};
+obsolete(crypto, blowfish_cbc_decrypt, 3) ->
+ {removed, "use crypto:block_decrypt/4 instead"};
+obsolete(crypto, blowfish_cbc_encrypt, 3) ->
+ {removed, "use crypto:block_encrypt/4 instead"};
+obsolete(crypto, blowfish_cfb64_decrypt, 3) ->
+ {removed, "use crypto:block_decrypt/4 instead"};
+obsolete(crypto, blowfish_cfb64_encrypt, 3) ->
+ {removed, "use crypto:block_encrypt/4 instead"};
+obsolete(crypto, blowfish_ecb_decrypt, 2) ->
+ {removed, "use crypto:block_decrypt/3 instead"};
+obsolete(crypto, blowfish_ecb_encrypt, 2) ->
+ {removed, "use crypto:block_encrypt/3 instead"};
+obsolete(crypto, blowfish_ofb64_decrypt, 3) ->
+ {removed, "use crypto:block_decrypt/4 instead"};
+obsolete(crypto, blowfish_ofb64_encrypt, 3) ->
+ {removed, "use crypto:block_encrypt/4 instead"};
+obsolete(crypto, des3_cbc_decrypt, 5) ->
+ {removed, "use crypto:block_decrypt/4 instead"};
+obsolete(crypto, des3_cbc_encrypt, 5) ->
+ {removed, "use crypto:block_encrypt/4 instead"};
+obsolete(crypto, des3_cfb_decrypt, 5) ->
+ {removed, "use crypto:block_decrypt/4 instead"};
+obsolete(crypto, des3_cfb_encrypt, 5) ->
+ {removed, "use crypto:block_encrypt/4 instead"};
+obsolete(crypto, des3_ede3_cbc_decrypt, 5) ->
+ {removed, "use crypto:block_decrypt/4 instead"};
+obsolete(crypto, des_cbc_decrypt, 3) ->
+ {removed, "use crypto:block_decrypt/4 instead"};
+obsolete(crypto, des_cbc_encrypt, 3) ->
+ {removed, "use crypto:block_encrypt/4 instead"};
+obsolete(crypto, des_cbc_ivec, 2) ->
+ {removed, "use crypto:next_iv/2 instead"};
+obsolete(crypto, des_cfb_decrypt, 3) ->
+ {removed, "use crypto:block_decrypt/4 instead"};
+obsolete(crypto, des_cfb_encrypt, 3) ->
+ {removed, "use crypto:block_encrypt/4 instead"};
+obsolete(crypto, des_cfb_ivec, 2) ->
+ {removed, "use crypto:next_iv/3 instead"};
+obsolete(crypto, des_ecb_decrypt, 2) ->
+ {removed, "use crypto:block_decrypt/3 instead"};
+obsolete(crypto, des_ecb_encrypt, 2) ->
+ {removed, "use crypto:block_encrypt/3 instead"};
+obsolete(crypto, des_ede3_cbc_encrypt, 5) ->
+ {removed, "use crypto:block_encrypt/4 instead"};
+obsolete(crypto, dh_compute_key, 3) ->
+ {removed, "use crypto:compute_key/4 instead"};
+obsolete(crypto, dh_generate_key, 1) ->
+ {removed, "use crypto:generate_key/2 instead"};
+obsolete(crypto, dh_generate_key, 2) ->
+ {removed, "use crypto:generate_key/3 instead"};
+obsolete(crypto, erlint, 1) ->
+ {removed, "only needed by other removed functions"};
+obsolete(crypto, info, 0) ->
+ {removed, "use crypto:module_info/0 instead"};
+obsolete(crypto, md4, 1) ->
+ {removed, "use crypto:hash/2 instead"};
+obsolete(crypto, md4_final, 1) ->
+ {removed, "use crypto:hash_final/1 instead"};
+obsolete(crypto, md4_init, 0) ->
+ {removed, "use crypto:hash_init/1 instead"};
+obsolete(crypto, md4_update, 2) ->
+ {removed, "use crypto:hash_update/2 instead"};
+obsolete(crypto, md5, 1) ->
+ {removed, "use crypto:hash/2 instead"};
+obsolete(crypto, md5_final, 1) ->
+ {removed, "use crypto:hash_final/1 instead"};
+obsolete(crypto, md5_init, 0) ->
+ {removed, "use crypto:hash_init/1 instead"};
+obsolete(crypto, md5_mac, 2) ->
+ {removed, "use crypto:hmac/3 instead"};
+obsolete(crypto, md5_mac_96, 2) ->
+ {removed, "use crypto:hmac/4 instead"};
+obsolete(crypto, md5_update, 2) ->
+ {removed, "use crypto:hash_update/2 instead"};
+obsolete(crypto, mod_exp, 3) ->
+ {removed, "use crypto:mod_pow/3 instead"};
+obsolete(crypto, mpint, 1) ->
+ {removed, "only needed by other removed functions"};
+obsolete(crypto, rand_bytes, 1) ->
+ {removed, "use crypto:strong_rand_bytes/1 instead"};
+obsolete(crypto, rc2_40_cbc_decrypt, 3) ->
+ {removed, "use crypto:block_decrypt/4 instead"};
+obsolete(crypto, rc2_40_cbc_encrypt, 3) ->
+ {removed, "use crypto:block_encrypt/4 instead"};
+obsolete(crypto, rc2_cbc_decrypt, 3) ->
+ {removed, "use crypto:block_decrypt/4 instead"};
+obsolete(crypto, rc2_cbc_encrypt, 3) ->
+ {removed, "use crypto:block_encrypt/4 instead"};
+obsolete(crypto, rc4_encrypt, 2) ->
+ {removed, "use crypto:stream_encrypt/2 instead"};
+obsolete(crypto, rc4_encrypt_with_state, 2) ->
+ {removed, "use crypto:stream_encrypt/2 instead"};
+obsolete(crypto, rc4_set_key, 2) ->
+ {removed, "use crypto:stream_init/2 instead"};
+obsolete(crypto, sha, 1) ->
+ {removed, "use crypto:hash/2 instead"};
+obsolete(crypto, sha_final, 1) ->
+ {removed, "use crypto:hash_final/1 instead"};
+obsolete(crypto, sha_init, 0) ->
+ {removed, "use crypto:hash_init/1 instead"};
+obsolete(crypto, sha_mac, 2) ->
+ {removed, "use crypto:hmac/3 instead"};
+obsolete(crypto, sha_mac, 3) ->
+ {removed, "use crypto:hmac/4 instead"};
+obsolete(crypto, sha_mac_96, 2) ->
+ {removed, "use crypto:hmac/4 instead"};
+obsolete(crypto, sha_update, 2) ->
+ {removed, "use crypto:hash_update/2 instead"};
+obsolete(crypto, strong_rand_mpint, 3) ->
+ {removed, "only needed by other removed functions"};
+obsolete(erl_lint, modify_line, 2) ->
+ {removed, "use erl_parse:map_anno/2 instead"};
+obsolete(erl_parse, get_attribute, 2) ->
+ {removed, "erl_anno:{column,line,location,text}/1 instead"};
+obsolete(erl_parse, get_attributes, 1) ->
+ {removed, "erl_anno:{column,line,location,text}/1 instead"};
+obsolete(erl_parse, set_line, 2) ->
+ {removed, "use erl_anno:set_line/2"};
+obsolete(erl_scan, set_attribute, 3) ->
+ {removed, "use erl_anno:set_line/2 instead"};
+obsolete(erlang, hash, 2) ->
+ {removed, "use erlang:phash2/2 instead"};
+obsolete(httpd_conf, check_enum, 2) ->
+ {removed, "use lists:member/2 instead"};
+obsolete(httpd_conf, clean, 1) ->
+ {removed, "use sting:strip/1 instead or possibly the re module"};
+obsolete(httpd_conf, custom_clean, 3) ->
+ {removed, "use sting:strip/1 instead or possibly the re module"};
+obsolete(httpd_conf, is_directory, 1) ->
+ {removed, "use filelib:is_dir/1 instead"};
+obsolete(httpd_conf, is_file, 1) ->
+ {removed, "use filelib:is_file/1 instead"};
+obsolete(httpd_conf, make_integer, 1) ->
+ {removed, "use erlang:list_to_integer/1 instead"};
+obsolete(rpc, safe_multi_server_call, 2) ->
+ {removed, "use rpc:multi_server_call/2 instead"};
+obsolete(rpc, safe_multi_server_call, 3) ->
+ {removed, "use rpc:multi_server_call/3 instead"};
+obsolete(ssl, connection_info, 1) ->
+ {removed, "use ssl:connection_information/[1,2] instead"};
+obsolete(ssl, negotiated_next_protocol, 1) ->
+ {removed, "use ssl:negotiated_protocol/1 instead"};
+obsolete(auth, node_cookie, _) ->
+ {deprecated, "use erlang:set_cookie/2 and net_adm:ping/1 instead"};
+obsolete(crypto, next_iv, _) ->
+ {deprecated, "see the 'New and Old API' chapter of the CRYPTO User's guide"};
+obsolete(crypto, stream_init, _) ->
+ {deprecated, "use crypto:crypto_init/3 + crypto:crypto_update/2 + crypto:crypto_final/1 or crypto:crypto_one_time/4 instead"};
+obsolete(filename, find_src, _) ->
+ {deprecated, "use filelib:find_source/1,3 instead"};
+obsolete(ssl, ssl_accept, _) ->
+ {deprecated, "use ssl_handshake/1,2,3 instead"};
+obsolete(wxCalendarCtrl, enableYearChange, _) ->
+ {deprecated, "not available in wxWidgets-2.9 and later"};
+obsolete(asn1ct, decode, _) ->
+ {removed, "use Mod:decode/2 instead"};
+obsolete(asn1ct, encode, _) ->
+ {removed, "use Mod:encode/2 instead"};
+obsolete(crypto, dss_sign, _) ->
+ {removed, "use crypto:sign/4 instead"};
+obsolete(crypto, dss_verify, _) ->
+ {removed, "use crypto:verify/5 instead"};
+obsolete(crypto, rsa_sign, _) ->
+ {removed, "use crypto:sign/4 instead"};
+obsolete(crypto, rsa_verify, _) ->
+ {removed, "use crypto:verify/5 instead"};
+obsolete(erl_scan, attributes_info, _) ->
+ {removed, "erl_anno:{column,line,location,text}/1 instead"};
+obsolete(erl_scan, token_info, _) ->
+ {removed, "erl_scan:{category,column,line,location,symbol,text}/1 instead"};
+obsolete(gen_fsm, _, _) ->
+ {deprecated, "use the 'gen_statem' module instead"};
+obsolete(pg2, _, _) ->
+ {deprecated, "the 'pg2' module is deprecated and scheduled for removal in OTP 24; use 'pg' instead."};
+obsolete(random, _, _) ->
+ {deprecated, "use the 'rand' module instead"};
+obsolete(os_mon_mib, _, _) ->
+ {removed, "this module was removed in OTP 22.0"};
+obsolete(_,_,_) -> no.
-dialyzer({no_match, obsolete_type/3}).
-obsolete_type(Module, Name, NumberOfVariables) ->
- case obsolete_type_1(Module, Name, NumberOfVariables) of
- {deprecated=Tag,{_,_,_}=Replacement} ->
- {Tag,Replacement,"in a future release"};
- {_,String}=Ret when is_list(String) ->
- Ret;
- {_,_,_}=Ret ->
- Ret;
- no ->
- no
- end.
+obsolete_type(erl_scan, column, 0) ->
+ {removed, "use erl_anno:column() instead"};
+obsolete_type(erl_scan, line, 0) ->
+ {removed, "use erl_anno:line() instead"};
+obsolete_type(erl_scan, location, 0) ->
+ {removed, "use erl_anno:location() instead"};
+obsolete_type(_,_,_) -> no.
-obsolete_type_1(erl_scan,column,0) ->
- {removed,{erl_anno,column,0},"19.0"};
-obsolete_type_1(erl_scan,line,0) ->
- {removed,{erl_anno,line,0},"19.0"};
-obsolete_type_1(erl_scan,location,0) ->
- {removed,{erl_anno,location,0},"19.0"};
-obsolete_type_1(_,_,_) ->
- no.
diff --git a/lib/stdlib/src/otp_internal.hrl b/lib/stdlib/src/otp_internal.hrl
new file mode 100644
index 0000000000..ace1fa5cc1
--- /dev/null
+++ b/lib/stdlib/src/otp_internal.hrl
@@ -0,0 +1,36 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2020. 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.
+%% You may obtain a copy of the License at
+%%
+%% http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+
+%%
+%% This file is included by the file "otp_internal.erl", which is
+%% auto-generated by stdlib/scripts/update_deprecations
+%%
+
+-export([obsolete/3, obsolete_type/3]).
+
+-type tag() :: 'deprecated' | 'removed'. %% | 'experimental'.
+-type mfas() :: mfa() | {atom(), atom(), [byte()]}.
+-type release() :: string().
+
+-spec obsolete(module(), atom(), arity()) ->
+ 'no' | {tag(), string()} | {tag(), mfas(), release()}.
+
+-spec obsolete_type(module(), atom(), arity()) ->
+ 'no' | {tag(), string()} | {tag(), mfas(), release()}.
diff --git a/lib/stdlib/src/proc_lib.erl b/lib/stdlib/src/proc_lib.erl
index cfbaf8b242..58e6faf950 100644
--- a/lib/stdlib/src/proc_lib.erl
+++ b/lib/stdlib/src/proc_lib.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2018. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2019. 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.
@@ -28,6 +28,7 @@
spawn/3, spawn_link/3, spawn/4, spawn_link/4,
spawn_opt/2, spawn_opt/3, spawn_opt/4, spawn_opt/5,
start/3, start/4, start/5, start_link/3, start_link/4, start_link/5,
+ start_monitor/3, start_monitor/4, start_monitor/5,
hibernate/3,
init_ack/1, init_ack/2,
init_p/3,init_p/5,format/1,format/2,format/3,report_cb/2,
@@ -39,25 +40,21 @@
-export([wake_up/3]).
-export_type([spawn_option/0]).
+-export_type([start_spawn_option/0]).
-include("logger.hrl").
%%-----------------------------------------------------------------------------
--type priority_level() :: 'high' | 'low' | 'max' | 'normal'.
--type max_heap_size() :: non_neg_integer() |
- #{ size => non_neg_integer(),
- kill => true,
- error_logger => true}.
--type spawn_option() :: 'link'
- | 'monitor'
- | {'priority', priority_level()}
- | {'max_heap_size', max_heap_size()}
- | {'min_heap_size', non_neg_integer()}
- | {'min_bin_vheap_size', non_neg_integer()}
- | {'fullsweep_after', non_neg_integer()}
- | {'message_queue_data',
- 'off_heap' | 'on_heap' | 'mixed' }.
+-type start_spawn_option() :: 'link'
+ | {'priority', erlang:priority_level()}
+ | {'max_heap_size', erlang:max_heap_size()}
+ | {'min_heap_size', non_neg_integer()}
+ | {'min_bin_vheap_size', non_neg_integer()}
+ | {'fullsweep_after', non_neg_integer()}
+ | {'message_queue_data', erlang:message_queue_data() }.
+
+-type spawn_option() :: erlang:spawn_opt_option().
-type dict_or_pid() :: pid()
| (ProcInfo :: [_])
@@ -65,6 +62,14 @@
%%-----------------------------------------------------------------------------
+-define(VERIFY_NO_MONITOR_OPT(M, F, A, T, Opts),
+ case lists:member(monitor, Opts) of
+ true -> erlang:error(badarg, [M,F,A,T,Opts]);
+ false -> ok
+ end).
+
+%%-----------------------------------------------------------------------------
+
-spec spawn(Fun) -> pid() when
Fun :: function().
@@ -141,17 +146,16 @@ spawn_link(Node, M, F, A) when is_atom(M), is_atom(F), is_list(A) ->
Ancestors = get_ancestors(),
erlang:spawn_link(Node, ?MODULE, init_p, [Parent,Ancestors,M,F,A]).
--spec spawn_opt(Fun, SpawnOpts) -> pid() when
+-spec spawn_opt(Fun, SpawnOpts) -> pid() | {pid(), reference()} when
Fun :: function(),
SpawnOpts :: [spawn_option()].
spawn_opt(F, Opts) when is_function(F) ->
Parent = get_my_name(),
Ancestors = get_ancestors(),
- check_for_monitor(Opts),
erlang:spawn_opt(?MODULE, init_p, [Parent,Ancestors,F],Opts).
--spec spawn_opt(Node, Function, SpawnOpts) -> pid() when
+-spec spawn_opt(Node, Function, SpawnOpts) -> pid() | {pid(), reference()} when
Node :: node(),
Function :: function(),
SpawnOpts :: [spawn_option()].
@@ -159,10 +163,9 @@ spawn_opt(F, Opts) when is_function(F) ->
spawn_opt(Node, F, Opts) when is_function(F) ->
Parent = get_my_name(),
Ancestors = get_ancestors(),
- check_for_monitor(Opts),
erlang:spawn_opt(Node, ?MODULE, init_p, [Parent,Ancestors,F], Opts).
--spec spawn_opt(Module, Function, Args, SpawnOpts) -> pid() when
+-spec spawn_opt(Module, Function, Args, SpawnOpts) -> pid() | {pid(), reference()} when
Module :: module(),
Function :: atom(),
Args :: [term()],
@@ -171,10 +174,9 @@ spawn_opt(Node, F, Opts) when is_function(F) ->
spawn_opt(M, F, A, Opts) when is_atom(M), is_atom(F), is_list(A) ->
Parent = get_my_name(),
Ancestors = get_ancestors(),
- check_for_monitor(Opts),
erlang:spawn_opt(?MODULE, init_p, [Parent,Ancestors,M,F,A], Opts).
--spec spawn_opt(Node, Module, Function, Args, SpawnOpts) -> pid() when
+-spec spawn_opt(Node, Module, Function, Args, SpawnOpts) -> pid() | {pid(), reference()} when
Node :: node(),
Module :: module(),
Function :: atom(),
@@ -184,30 +186,13 @@ spawn_opt(M, F, A, Opts) when is_atom(M), is_atom(F), is_list(A) ->
spawn_opt(Node, M, F, A, Opts) when is_atom(M), is_atom(F), is_list(A) ->
Parent = get_my_name(),
Ancestors = get_ancestors(),
- check_for_monitor(Opts),
erlang:spawn_opt(Node, ?MODULE, init_p, [Parent,Ancestors,M,F,A], Opts).
-%% OTP-6345
-%% monitor spawn_opt option is currently not possible to use
-check_for_monitor(SpawnOpts) ->
- case lists:member(monitor, SpawnOpts) of
- true ->
- erlang:error(badarg);
- false ->
- false
- end.
-
spawn_mon(M,F,A) ->
Parent = get_my_name(),
Ancestors = get_ancestors(),
erlang:spawn_monitor(?MODULE, init_p, [Parent,Ancestors,M,F,A]).
-spawn_opt_mon(M, F, A, Opts) when is_atom(M), is_atom(F), is_list(A) ->
- Parent = get_my_name(),
- Ancestors = get_ancestors(),
- check_for_monitor(Opts),
- erlang:spawn_opt(?MODULE, init_p, [Parent,Ancestors,M,F,A], [monitor|Opts]).
-
-spec hibernate(Module, Function, Args) -> no_return() when
Module :: module(),
Function :: atom(),
@@ -216,14 +201,6 @@ spawn_opt_mon(M, F, A, Opts) when is_atom(M), is_atom(F), is_list(A) ->
hibernate(M, F, A) when is_atom(M), is_atom(F), is_list(A) ->
erlang:hibernate(?MODULE, wake_up, [M, F, A]).
-ensure_link(SpawnOpts) ->
- case lists:member(link, SpawnOpts) of
- true ->
- SpawnOpts;
- false ->
- [link|SpawnOpts]
- end.
-
-spec init_p(pid(), [pid()], function()) -> term().
init_p(Parent, Ancestors, Fun) when is_function(Fun) ->
@@ -299,20 +276,32 @@ start(M, F, A) when is_atom(M), is_atom(F), is_list(A) ->
Ret :: term() | {error, Reason :: term()}.
start(M, F, A, Timeout) when is_atom(M), is_atom(F), is_list(A) ->
- PidRef = spawn_mon(M, F, A),
- sync_wait_mon(PidRef, Timeout).
+ sync_start(spawn_mon(M, F, A), Timeout).
-spec start(Module, Function, Args, Time, SpawnOpts) -> Ret when
Module :: module(),
Function :: atom(),
Args :: [term()],
Time :: timeout(),
- SpawnOpts :: [spawn_option()],
+ SpawnOpts :: [start_spawn_option()],
Ret :: term() | {error, Reason :: term()}.
start(M, F, A, Timeout, SpawnOpts) when is_atom(M), is_atom(F), is_list(A) ->
- PidRef = spawn_opt_mon(M, F, A, SpawnOpts),
- sync_wait_mon(PidRef, Timeout).
+ ?VERIFY_NO_MONITOR_OPT(M, F, A, Timeout, SpawnOpts),
+ sync_start(?MODULE:spawn_opt(M, F, A, [monitor|SpawnOpts]), Timeout).
+
+sync_start({Pid, Ref}, Timeout) ->
+ receive
+ {ack, Pid, Return} ->
+ erlang:demonitor(Ref, [flush]),
+ Return;
+ {'DOWN', Ref, process, Pid, Reason} ->
+ {error, Reason}
+ after Timeout ->
+ erlang:demonitor(Ref, [flush]),
+ kill_flush(Pid),
+ {error, timeout}
+ end.
-spec start_link(Module, Function, Args) -> Ret when
Module :: module(),
@@ -331,60 +320,88 @@ start_link(M, F, A) when is_atom(M), is_atom(F), is_list(A) ->
Ret :: term() | {error, Reason :: term()}.
start_link(M, F, A, Timeout) when is_atom(M), is_atom(F), is_list(A) ->
- Pid = ?MODULE:spawn_link(M, F, A),
- sync_wait(Pid, Timeout).
+ sync_start_link(?MODULE:spawn_link(M, F, A), Timeout).
-spec start_link(Module, Function, Args, Time, SpawnOpts) -> Ret when
Module :: module(),
Function :: atom(),
Args :: [term()],
Time :: timeout(),
- SpawnOpts :: [spawn_option()],
+ SpawnOpts :: [start_spawn_option()],
Ret :: term() | {error, Reason :: term()}.
start_link(M,F,A,Timeout,SpawnOpts) when is_atom(M), is_atom(F), is_list(A) ->
- Pid = ?MODULE:spawn_opt(M, F, A, ensure_link(SpawnOpts)),
- sync_wait(Pid, Timeout).
+ ?VERIFY_NO_MONITOR_OPT(M, F, A, Timeout, SpawnOpts),
+ sync_start_link(?MODULE:spawn_opt(M, F, A, [link|SpawnOpts]), Timeout).
-sync_wait(Pid, Timeout) ->
+sync_start_link(Pid, Timeout) ->
receive
{ack, Pid, Return} ->
- Return;
+ Return;
{'EXIT', Pid, Reason} ->
- {error, Reason}
+ {error, Reason}
after Timeout ->
- unlink(Pid),
- exit(Pid, kill),
- flush(Pid),
- {error, timeout}
+ kill_flush(Pid),
+ {error, timeout}
end.
-sync_wait_mon({Pid, Ref}, Timeout) ->
+-spec start_monitor(Module, Function, Args) -> {Ret, Mon} when
+ Module :: module(),
+ Function :: atom(),
+ Args :: [term()],
+ Mon :: reference(),
+ Ret :: term() | {error, Reason :: term()}.
+
+start_monitor(M, F, A) when is_atom(M), is_atom(F), is_list(A) ->
+ start_monitor(M, F, A, infinity).
+
+-spec start_monitor(Module, Function, Args, Time) -> {Ret, Mon} when
+ Module :: module(),
+ Function :: atom(),
+ Args :: [term()],
+ Time :: timeout(),
+ Mon :: reference(),
+ Ret :: term() | {error, Reason :: term()}.
+
+start_monitor(M, F, A, Timeout) when is_atom(M), is_atom(F), is_list(A) ->
+ sync_start_monitor(spawn_mon(M, F, A), Timeout).
+
+-spec start_monitor(Module, Function, Args, Time, SpawnOpts) -> {Ret, Mon} when
+ Module :: module(),
+ Function :: atom(),
+ Args :: [term()],
+ Time :: timeout(),
+ SpawnOpts :: [start_spawn_option()],
+ Mon :: reference(),
+ Ret :: term() | {error, Reason :: term()}.
+
+start_monitor(M,F,A,Timeout,SpawnOpts) when is_atom(M),
+ is_atom(F),
+ is_list(A) ->
+ ?VERIFY_NO_MONITOR_OPT(M, F, A, Timeout, SpawnOpts),
+ sync_start_monitor(?MODULE:spawn_opt(M, F, A, [monitor|SpawnOpts]),
+ Timeout).
+
+sync_start_monitor({Pid, Ref}, Timeout) ->
receive
{ack, Pid, Return} ->
- erlang:demonitor(Ref, [flush]),
- Return;
- {'DOWN', Ref, _Type, Pid, Reason} ->
- {error, Reason};
- {'EXIT', Pid, Reason} -> %% link as spawn_opt?
- erlang:demonitor(Ref, [flush]),
- {error, Reason}
+ {Return, Ref};
+ {'DOWN', Ref, process, Pid, Reason} = Down ->
+ self() ! Down,
+ {{error, Reason}, Ref}
after Timeout ->
- erlang:demonitor(Ref, [flush]),
- exit(Pid, kill),
- flush(Pid),
- {error, timeout}
+ kill_flush(Pid),
+ {{error, timeout}, Ref}
end.
--spec flush(pid()) -> 'true'.
+-spec kill_flush(Pid) -> 'ok' when
+ Pid :: pid().
-flush(Pid) ->
- receive
- {'EXIT', Pid, _} ->
- true
- after 0 ->
- true
- end.
+kill_flush(Pid) ->
+ unlink(Pid),
+ exit(Pid, kill),
+ receive {'EXIT', Pid, _} -> ok after 0 -> ok end,
+ ok.
-spec init_ack(Parent, Ret) -> 'ok' when
Parent :: pid(),
@@ -784,20 +801,114 @@ format(CrashReport, Encoding, Depth) ->
encoding => Encoding,
single_line => false}).
-do_format([OwnReport,LinkReport], #{single_line:=Single}=Extra) ->
+do_format([OwnReport,LinkReport], Extra) ->
+ #{encoding:=Enc, single_line:=Single, chars_limit:=Limit0} = Extra,
Indent = if Single -> "";
true -> " "
end,
- MyIndent = Indent ++ Indent,
- Sep = nl(Single,"; "),
- OwnFormat = format_report(OwnReport, MyIndent, Extra),
- LinkFormat = lists:join(Sep,format_link_report(LinkReport, MyIndent, Extra)),
Nl = nl(Single," "),
- Str = io_lib:format("~scrasher:"++Nl++"~ts"++Sep++"~sneighbours:"++Nl++"~ts",
- [Indent,OwnFormat,Indent,LinkFormat]),
- lists:flatten(Str).
+ Sep = nl(Single, report_separator()),
+ {PartLimit, Limit} =
+ case Limit0 of
+ unlimited ->
+ {Limit0, Limit0};
+ _ when is_integer(Limit0) ->
+ %% HardcodedSize is the length of the hardcoded heading +
+ %% separators in the final format string below,
+ %% including neighbours. Just make sure the limit
+ %% does not become negative.
+ Num = length(OwnReport),
+ HardcodedSize = (length(Indent) + length("crasher")
+ + length(Nl) + length(Sep)
+ + (length(Sep) * Num)),
+ Limit1 = max(Limit0-HardcodedSize, 1),
+
+ %% Divide the available characters over all report
+ %% parts. Spend one third of the characters on the
+ %% crash reason, and let the rest of the elements
+ %% (including the neighbours) share the other two
+ %% thirds. This is to make sure we see a good part of
+ %% the crash reason. Most of the other elements in the
+ %% crasher's report are quite small, so we don't loose
+ %% a lot of info from these anyway.
+ EL = Limit1 div 3,
+ PL = (Limit1-EL) div (Num),
+ {PL, Limit1}
+ end,
+ LinkFormat = format_link_reports(LinkReport, Indent, Extra, PartLimit),
+ LinkFormatSize = size(Enc, LinkFormat),
+
+ OwnFormat = format_own_report(OwnReport, Indent, Extra,
+ LinkFormatSize, PartLimit, Limit),
+ io_lib:format("~scrasher:"++Nl++"~ts"++Sep++"~ts",
+ [Indent,OwnFormat,LinkFormat]).
+
+format_own_report(OwnReport, Indent, Extra, LinkFormatSize, PartLimit, Limit0) ->
+ MyIndent = Indent ++ Indent,
+ case separate_error_info(OwnReport) of
+ {First,{Class,Reason,StackTrace},Rest} ->
+ F = format_report(First, MyIndent, Extra, PartLimit),
+ R = format_report(Rest, MyIndent, Extra, PartLimit),
+ #{encoding:=Enc, single_line:=Single} = Extra,
+ Sep = nl(Single, part_separator()),
+ Limit = case Limit0 of
+ unlimited ->
+ Limit0;
+ _ when is_integer(Limit0) ->
+ %% Some of the report parts are quite small,
+ %% and we can use the leftover chars to show
+ %% more of the error_info part.
+ SizeOfOther = (size(Enc, F)
+ +size(Enc, R)
+ -length(Sep)*(length(F)+length(R))
+ +LinkFormatSize),
+ max(Limit0-SizeOfOther, 1)
+ end,
+ EI = format_exception(Class, Reason, StackTrace, Extra, Limit),
+ lists:join(Sep, [F, EI, R]);
+ no ->
+ Limit = case Limit0 of
+ unlimited ->
+ Limit0;
+ _ when is_integer(Limit0) ->
+ max(Limit0-LinkFormatSize, 1)
+ end,
+ format_report(OwnReport, MyIndent, Extra, Limit)
+ end.
-format_link_report([Link|Reps], Indent0, #{single_line:=Single}=Extra) ->
+separate_error_info(Report) ->
+ try
+ lists:splitwith(fun(A) -> element(1, A) =/= error_info end, Report)
+ of
+ {First, [{error_info,ErrorInfo}|Rest]} ->
+ {First,ErrorInfo,Rest};
+ _ -> no
+ catch _:_ -> no
+ end.
+
+%% If the size of the total report is limited by chars_limit, then
+%% print only the pids.
+format_link_reports(LinkReports, Indent, Extra, PartLimit)
+ when is_integer(PartLimit) ->
+ #{encoding:=Enc, depth:=Depth, single_line:=Single} = Extra,
+ Pids = [P || {neighbour,[{pid,P}|_]} <- LinkReports],
+ {P,Tl} = p(Enc,Depth),
+ Width = if Single -> "0";
+ true -> ""
+ end,
+ io_lib:format(Indent++"neighbours: ~"++Width++P,
+ [Pids|Tl],
+ [{chars_limit,PartLimit}]);
+format_link_reports(LinkReports, Indent, Extra, PartLimit) ->
+ #{single_line:=Single} = Extra,
+ MyIndent = Indent ++ Indent,
+ LinkFormat =
+ lists:join(nl(Single, report_separator()),
+ format_link_report(LinkReports, MyIndent, Extra, PartLimit)),
+ [Indent,"neighbours:",nl(Single," "),LinkFormat].
+
+format_link_report([Link|Reps], Indent0, Extra, PartLimit) ->
+ #{single_line:=Single} = Extra,
Rep = case Link of
{neighbour,Rep0} -> Rep0;
_ -> Link
@@ -806,63 +917,70 @@ format_link_report([Link|Reps], Indent0, #{single_line:=Single}=Extra) ->
true -> Indent0
end,
LinkIndent = [" ",Indent],
- [[Indent,"neighbour:",nl(Single," "),format_report(Rep, LinkIndent, Extra)]|
- format_link_report(Reps, Indent, Extra)];
-format_link_report(Rep, Indent, Extra) ->
- format_report(Rep, Indent, Extra).
-
-format_report(Rep, Indent, #{single_line:=Single}=Extra) when is_list(Rep) ->
- lists:join(nl(Single,", "),format_rep(Rep, Indent, Extra));
-format_report(Rep, Indent0, #{encoding:=Enc,depth:=Depth,
- chars_limit:=Limit,single_line:=Single}) ->
+ [[Indent,"neighbour:",nl(Single," "),
+ format_report(Rep, LinkIndent, Extra, PartLimit)]|
+ format_link_report(Reps, Indent, Extra, PartLimit)];
+format_link_report(Rep, Indent, Extra, PartLimit) ->
+ format_report(Rep, Indent, Extra, PartLimit).
+
+format_report(Rep, Indent, Extra, Limit) when is_list(Rep) ->
+ #{single_line:=Single} = Extra,
+ lists:join(nl(Single, part_separator()),
+ format_rep(Rep, Indent, Extra, Limit));
+format_report(Rep, Indent0, Extra, Limit) ->
+ #{encoding:=Enc, depth:=Depth, single_line:=Single} = Extra,
{P,Tl} = p(Enc,Depth),
{Indent,Width} = if Single -> {"","0"};
true -> {Indent0,""}
end,
- Opts = if is_integer(Limit) -> [{chars_limit,Limit}];
- true -> []
- end,
+ Opts = chars_limit_opt(Limit),
io_lib:format("~s~"++Width++P, [Indent, Rep | Tl], Opts).
-format_rep([{initial_call,InitialCall}|Rep], Indent, Extra) ->
- [format_mfa(Indent, InitialCall, Extra)|format_rep(Rep, Indent, Extra)];
-format_rep([{error_info,{Class,Reason,StackTrace}}|Rep], Indent, Extra) ->
- [format_exception(Class, Reason, StackTrace, Extra)|
- format_rep(Rep, Indent, Extra)];
-format_rep([{Tag,Data}|Rep], Indent, Extra) ->
- [format_tag(Indent, Tag, Data, Extra)|format_rep(Rep, Indent, Extra)];
-format_rep(_, _, _Extra) ->
+format_rep([{initial_call,InitialCall}|Rep], Indent, Extra, Limit) ->
+ [format_mfa(Indent, InitialCall, Extra, Limit)|
+ format_rep(Rep, Indent, Extra, Limit)];
+format_rep([{Tag,Data}|Rep], Indent, Extra, Limit) ->
+ [format_tag(Indent, Tag, Data, Extra, Limit)|
+ format_rep(Rep, Indent, Extra, Limit)];
+format_rep(_, _, _Extra, _Limit) ->
[].
-format_exception(Class, Reason, StackTrace,
- #{encoding:=Enc,depth:=Depth,chars_limit:=Limit,
- single_line:=Single}=Extra) ->
- PF = pp_fun(Extra),
+format_exception(Class, Reason, StackTrace, Extra, Limit) ->
+ #{encoding:=Enc,depth:=Depth, single_line:=Single} = Extra,
StackFun = fun(M, _F, _A) -> (M =:= erl_eval) or (M =:= ?MODULE) end,
if Single ->
{P,Tl} = p(Enc,Depth),
- Opts = if is_integer(Limit) -> [{chars_limit,Limit}];
- true -> []
- end,
+ Opts = chars_limit_opt(Limit),
[atom_to_list(Class), ": ",
io_lib:format("~0"++P,[{Reason,StackTrace}|Tl],Opts)];
true ->
+ %% Notice that each call to PF uses chars_limit, which
+ %% means that the total size of the formatted exception
+ %% can exceed the limit a lot.
+ PF = pp_fun(Extra, Enc),
EI = " ",
- [EI, erl_error:format_exception(1+length(EI), Class, Reason,
- StackTrace, StackFun, PF, Enc)]
+ Lim = case Limit of
+ unlimited -> -1;
+ _ -> Limit
+ end,
+ FE = erl_error:format_exception(1+length(EI), Class, Reason,
+ StackTrace, StackFun, PF, Enc,
+ Lim),
+ [EI, FE]
end.
-format_mfa(Indent0, {M,F,Args}=StartF, #{encoding:=Enc,single_line:=Single}=Extra) ->
+format_mfa(Indent0, {M,F,Args}=StartF, Extra, Limit) ->
+ #{encoding:=Enc,single_line:=Single} = Extra,
Indent = if Single -> "";
true -> Indent0
end,
try
A = length(Args),
- [Indent,"initial call: ",atom_to_list(M),$:,to_string(F, Enc),$/,
+ [Indent,"initial call: ",to_string(M, Enc),$:,to_string(F, Enc),$/,
integer_to_list(A)]
catch
error:_ ->
- format_tag(Indent, initial_call, StartF, Extra)
+ format_tag(Indent, initial_call, StartF, Extra, Limit)
end.
to_string(A, latin1) ->
@@ -870,27 +988,25 @@ to_string(A, latin1) ->
to_string(A, _) ->
io_lib:write_atom(A).
-pp_fun(#{encoding:=Enc,depth:=Depth,chars_limit:=Limit,single_line:=Single}) ->
+pp_fun(Extra, Enc) ->
+ #{encoding:=Enc,depth:=Depth, single_line:=Single} = Extra,
{P,Tl} = p(Enc, Depth),
Width = if Single -> "0";
true -> ""
end,
- Opts = if is_integer(Limit) -> [{chars_limit,Limit}];
- true -> []
- end,
- fun(Term, I) ->
- io_lib:format("~" ++ Width ++ "." ++ integer_to_list(I) ++ P,
- [Term|Tl], Opts)
+ fun(Term, I, Limit) ->
+ S = io_lib:format("~" ++ Width ++ "." ++ integer_to_list(I) ++ P,
+ [Term|Tl], [{chars_limit, Limit}]),
+ {S, sub(Limit, S, Enc)}
end.
-format_tag(Indent0, Tag, Data, #{encoding:=Enc,depth:=Depth,chars_limit:=Limit,single_line:=Single}) ->
+format_tag(Indent0, Tag, Data, Extra, Limit) ->
+ #{encoding:=Enc,depth:=Depth,single_line:=Single} = Extra,
{P,Tl} = p(Enc, Depth),
{Indent,Width} = if Single -> {"","0"};
true -> {Indent0,""}
end,
- Opts = if is_integer(Limit) -> [{chars_limit,Limit}];
- true -> []
- end,
+ Opts = chars_limit_opt(Limit),
io_lib:format("~s~" ++ Width ++ "p: ~" ++ Width ++ ".18" ++ P,
[Indent, Tag, Data|Tl], Opts).
@@ -902,12 +1018,35 @@ p(Encoding, Depth) ->
P = modifier(Encoding) ++ Letter,
{P, Tl}.
+report_separator() -> "; ".
+
+part_separator() -> ", ".
+
+chars_limit_opt(CharsLimit) ->
+ [{chars_limit, CharsLimit} || is_integer(CharsLimit)].
+
modifier(latin1) -> "";
modifier(_) -> "t".
nl(true,Else) -> Else;
nl(false,_) -> "\n".
+%% Make sure T does change sign.
+sub(T, _, _Enc) when T < 0 -> T;
+sub(T, E, Enc) ->
+ Sz = size(Enc, E),
+ if
+ T >= Sz ->
+ T - Sz;
+ true ->
+ 0
+ end.
+
+size(latin1, S) ->
+ iolist_size(S);
+size(_, S) ->
+ string:length(S).
+
%%% -----------------------------------------------------------
%%% Stop a process and wait for it to terminate
%%% -----------------------------------------------------------
diff --git a/lib/stdlib/src/proplists.erl b/lib/stdlib/src/proplists.erl
index 3ce68887ae..9216c3bdb3 100644
--- a/lib/stdlib/src/proplists.erl
+++ b/lib/stdlib/src/proplists.erl
@@ -220,7 +220,7 @@ get_value(Key, [P | Ps], Default) ->
{_, Value} ->
Value;
_ ->
- %% Don</code>t continue the search!
+ %% Don't continue the search!
Default
end;
true ->
@@ -419,7 +419,7 @@ substitute_aliases_1([], P) ->
%% <p>Example: <code>substitute_negations([{no_foo, foo}], L)</code>
%% will replace any atom <code>no_foo</code> or tuple <code>{no_foo,
%% true}</code> in <code>L</code> with <code>{foo, false}</code>, and
-%% any other tuple <code>{no_foo, ...}</code> with <code>foo</code.</p>
+%% any other tuple <code>{no_foo, ...}</code> with <code>foo</code>.</p>
%%
%% @see get_bool/2
%% @see substitute_aliases/2
@@ -639,24 +639,24 @@ normalize(L, []) ->
Rest :: [term()].
split(List, Keys) ->
- {Store, Rest} = split(List, dict:from_list([{K, []} || K <- Keys]), []),
- {[lists:reverse(dict:fetch(K, Store)) || K <- Keys],
+ {Store, Rest} = split(List, maps:from_list([{K, []} || K <- Keys]), []),
+ {[lists:reverse(map_get(K, Store)) || K <- Keys],
lists:reverse(Rest)}.
split([P | Ps], Store, Rest) ->
if is_atom(P) ->
- case dict:is_key(P, Store) of
+ case is_map_key(P, Store) of
true ->
- split(Ps, dict_prepend(P, P, Store), Rest);
+ split(Ps, maps_prepend(P, P, Store), Rest);
false ->
split(Ps, Store, [P | Rest])
end;
tuple_size(P) >= 1 ->
%% Note that Key does not have to be an atom in this case.
Key = element(1, P),
- case dict:is_key(Key, Store) of
+ case is_map_key(Key, Store) of
true ->
- split(Ps, dict_prepend(Key, P, Store), Rest);
+ split(Ps, maps_prepend(Key, P, Store), Rest);
false ->
split(Ps, Store, [P | Rest])
end;
@@ -666,5 +666,5 @@ split([P | Ps], Store, Rest) ->
split([], Store, Rest) ->
{Store, Rest}.
-dict_prepend(Key, Val, Dict) ->
- dict:store(Key, [Val | dict:fetch(Key, Dict)], Dict).
+maps_prepend(Key, Val, Dict) ->
+ Dict#{Key := [Val | map_get(Key, Dict)]}.
diff --git a/lib/stdlib/src/qlc.erl b/lib/stdlib/src/qlc.erl
index a1c1117e31..713ed1f896 100644
--- a/lib/stdlib/src/qlc.erl
+++ b/lib/stdlib/src/qlc.erl
@@ -785,7 +785,7 @@ merge_binding_structs(Bs1, Bs2) ->
aux_name1(Name, N, AllNames) ->
SN = name_suffix(Name, N),
- case sets:is_element(SN, AllNames) of
+ case gb_sets:is_member(SN, AllNames) of
true -> aux_name1(Name, N + 1, AllNames);
false -> {SN, N}
end.
@@ -1357,7 +1357,7 @@ flatten_abstr(E, VN, _Vars, Body) ->
{VN, Body, E}.
abstract_vars(Abstract) ->
- sets:from_list(ordsets:to_list(vars(Abstract))).
+ gb_sets:from_list(ordsets:to_list(vars(Abstract))).
collect([]=L) ->
L;
diff --git a/lib/stdlib/src/qlc_pt.erl b/lib/stdlib/src/qlc_pt.erl
index 4a39f8ae9d..7cf631d85d 100644
--- a/lib/stdlib/src/qlc_pt.erl
+++ b/lib/stdlib/src/qlc_pt.erl
@@ -511,7 +511,7 @@ used_genvar_check(FormsNoShadows, State) ->
Acc0 = {State#state.intro_vars, [{atom, anno0(), true}]},
{_, {[], Exprs}} = qual_fold(F, Acc0, [], FormsNoShadows, State),
FunctionNames = [Name || {function, _, Name, _, _} <- FormsNoShadows],
- UniqueFName = qlc:aux_name(used_genvar, 1, sets:from_list(FunctionNames)),
+ UniqueFName = qlc:aux_name(used_genvar, 1, gb_sets:from_list(FunctionNames)),
A = anno0(),
{function,A,UniqueFName,0,[{clause,A,[],[],lists:reverse(Exprs)}]}.
@@ -613,8 +613,8 @@ q_intro_vars(QId, [{QId, IVs} | QsIVs], IVsSoFar) -> {QsIVs, IVs ++ IVsSoFar}.
transform(FormsNoShadows, State) ->
_ = erlang:system_flag(backtrace_depth, 500),
IntroVars = State#state.intro_vars,
- AllVars = sets:from_list(ordsets:to_list(qlc:vars(FormsNoShadows))),
- ?DEBUG("AllVars = ~p~n", [sets:to_list(AllVars)]),
+ AllVars = gb_sets:from_list(ordsets:to_list(qlc:vars(FormsNoShadows))),
+ ?DEBUG("AllVars = ~p~n", [gb_sets:to_list(AllVars)]),
F1 = fun(QId, {generate,_,P,LE}, Foo, {GoI,SI}) ->
{{QId,GoI,SI,{gen,P,LE}},Foo,{GoI + 3, SI + 2}};
(QId, F, Foo, {GoI,SI}) ->
@@ -632,10 +632,10 @@ transform(FormsNoShadows, State) ->
{_,Source0} = qual_fold(fun(_QId, {generate,_,_P,_E}=Q, Dict, Foo) ->
{Q,Dict,Foo};
(QId, F, Dict, Foo) ->
- {F,dict:store(QId, F, Dict),Foo}
- end, dict:new(), [], FormsNoShadows, State),
+ {F,maps:put(QId, F, Dict),Foo}
+ end, maps:new(), [], FormsNoShadows, State),
{_,Source} = qlc_mapfold(fun(Id, {lc,_L,E,_Qs}=LC, Dict) ->
- {LC,dict:store(Id, E, Dict)}
+ {LC,maps:put(Id, E, Dict)}
end, Source0, FormsNoShadows, State),
@@ -685,7 +685,7 @@ transform(FormsNoShadows, State) ->
FunW = {'fun',L,{clauses,[{clause,L,AsW,[],
[{match,L,{var,L,Fun},FunC},
{call,L,{var,L,Fun},As0}]}]}},
- {ok, OrigE0} = dict:find(Id, Source),
+ OrigE0 = map_get(Id, Source),
OrigE = undo_no_shadows(OrigE0, State),
QCode = qcode(OrigE, XQCs, Source, L, State),
Qdata = qdata(XQCs, L),
@@ -2361,7 +2361,7 @@ qcode(E, QCs, Source, L, State) ->
qcode([{_QId, {_QIvs, {{gen,P,_LE,_GV}, GoI, _SI}}} | QCs], Source, State) ->
[{GoI,undo_no_shadows(P, State)} | qcode(QCs, Source, State)];
qcode([{QId, {_QIVs, {{fil,_F}, GoI, _SI}}} | QCs], Source, State) ->
- {ok,OrigF} = dict:find(QId, Source),
+ OrigF = map_get(QId, Source),
[{GoI,undo_no_shadows(OrigF, State)} | qcode(QCs, Source, State)];
qcode([], _Source, _State) ->
[].
@@ -2666,12 +2666,12 @@ no_shadows(Forms0, State) ->
%%
%% The original names of variables are kept in a table in State.
%% undo_no_shadows/2 re-creates the original code.
- AllVars = sets:from_list(ordsets:to_list(qlc:vars(Forms0))),
- ?DEBUG("nos AllVars = ~p~n", [sets:to_list(AllVars)]),
+ AllVars = gb_sets:from_list(ordsets:to_list(qlc:vars(Forms0))),
+ ?DEBUG("nos AllVars = ~p~n", [gb_sets:to_list(AllVars)]),
VFun = fun(_Id, LC, Vs) -> nos(LC, Vs) end,
LI = ets:new(?APIMOD,[]),
UV = ets:new(?APIMOD,[]),
- D0 = dict:new(),
+ D0 = maps:new(),
S1 = {LI, D0, UV, AllVars, [], State},
_ = qlc_mapfold(VFun, S1, Forms0, State),
?DEBUG("UsedIntroVars = ~p~n", [ets:match_object(UV, '_')]),
@@ -2781,7 +2781,7 @@ nos_var(Anno, Name, State) ->
end.
used_var(V, Vs, UV) ->
- case dict:find(V, Vs) of
+ case maps:find(V, Vs) of
{ok,Value} ->
VN = qlc:name_suffix(V, Value),
_ = ets:update_counter(UV, VN, 1),
@@ -2796,10 +2796,10 @@ next_var(V, Vs, AllVars, LI, UV) ->
end,
true = ets:insert(LI, {V, NValue}),
VN = qlc:name_suffix(V, NValue),
- case sets:is_element(VN, AllVars) of
+ case gb_sets:is_member(VN, AllVars) of
true -> next_var(V, Vs, AllVars, LI, UV);
false -> true = ets:insert(UV, {VN, 0}),
- NVs = dict:store(V, NValue, Vs),
+ NVs = maps:put(V, NValue, Vs),
{VN, NVs}
end.
diff --git a/lib/stdlib/src/queue.erl b/lib/stdlib/src/queue.erl
index 11c0aa8d2b..9fe3782f92 100644
--- a/lib/stdlib/src/queue.erl
+++ b/lib/stdlib/src/queue.erl
@@ -37,7 +37,7 @@
%% Mis-spelled, deprecated.
-export([lait/1]).
--deprecated([lait/1]).
+-deprecated([{lait,1,"use queue:liat/1 instead"}]).
%%--------------------------------------------------------------------------
%% Efficient implementation of double ended fifo queues
diff --git a/lib/stdlib/src/random.erl b/lib/stdlib/src/random.erl
index 46dabb4323..8d6a35f031 100644
--- a/lib/stdlib/src/random.erl
+++ b/lib/stdlib/src/random.erl
@@ -18,7 +18,7 @@
%% %CopyrightEnd%
%%
-module(random).
--deprecated(module).
+-deprecated({'_','_',"use the 'rand' module instead"}).
%% Reasonable random number generator.
%% The method is attributed to B. A. Wichmann and I. D. Hill
diff --git a/lib/stdlib/src/shell_default.erl b/lib/stdlib/src/shell_default.erl
index a0c1d98513..e65340e663 100644
--- a/lib/stdlib/src/shell_default.erl
+++ b/lib/stdlib/src/shell_default.erl
@@ -28,6 +28,7 @@
erlangrc/1,bi/1, regs/0, flush/0,pwd/0,ls/0,ls/1,cd/1,
y/1, y/2,
xm/1, bt/1, q/0,
+ h/1, h/2, h/3, ht/1, ht/2, ht/3,
ni/0, nregs/0]).
-export([ih/0,iv/0,im/0,ii/1,ii/2,iq/1,ini/1,ini/2,inq/1,ib/2,ib/3,
@@ -43,7 +44,13 @@ help() ->
format("e(N) -- repeat the expression in query <N>\n"),
format("f() -- forget all variable bindings\n"),
format("f(X) -- forget the binding of variable X\n"),
- format("h() -- history\n"),
+ format("h() -- history\n"),
+ format("h(Mod) -- help about module\n"),
+ format("h(Mod,Func)-- help about function in module\n"),
+ format("h(Mod,Func,Arity) -- help about function with arity in module\n"),
+ format("ht(Mod) -- help about a module's types\n"),
+ format("ht(Mod,Func) -- help about type in module\n"),
+ format("ht(Mod,Func,Arity) -- help about type with arity in module\n"),
format("history(N) -- set how many previous commands to keep\n"),
format("results(N) -- set how many previous command results to keep\n"),
format("catch_exception(B) -- how exceptions are handled\n"),
@@ -76,6 +83,12 @@ c(File, Opt, Filter) -> c:c(File, Opt, Filter).
cd(D) -> c:cd(D).
erlangrc(X) -> c:erlangrc(X).
flush() -> c:flush().
+h(M) -> c:h(M).
+h(M,F) -> c:h(M,F).
+h(M,F,A) -> c:h(M,F,A).
+ht(M) -> c:ht(M).
+ht(M,F) -> c:ht(M,F).
+ht(M,F,A) -> c:ht(M,F,A).
i() -> c:i().
i(X,Y,Z) -> c:i(X,Y,Z).
l(Mod) -> c:l(Mod).
diff --git a/lib/stdlib/src/shell_docs.erl b/lib/stdlib/src/shell_docs.erl
new file mode 100644
index 0000000000..6e56030fca
--- /dev/null
+++ b/lib/stdlib/src/shell_docs.erl
@@ -0,0 +1,684 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 1996-2018. 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.
+%% You may obtain a copy of the License at
+%%
+%% http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+-module(shell_docs).
+
+-include("eep48.hrl").
+
+-export([render/2, render/3, render/4]).
+-export([render_type/2, render_type/3, render_type/4]).
+
+%% Used by chunks.escript in erl_docgen
+-export([validate/1, normalize/1]).
+
+%% Convinience functions
+-export([get_doc/1, get_doc/3, get_type_doc/3]).
+
+-record(config, { docs,
+ io_opts = io:getopts(),
+ io_columns = element(2,io:columns())
+ }).
+
+-define(ALL_ELEMENTS,[a,p,h1,h2,h3,i,br,em,pre,code,ul,ol,li,dl,dt,dd]).
+%% inline elements are:
+-define(INLINE,[i,br,em,code,a]).
+-define(IS_INLINE(ELEM),(((ELEM) =:= a) orelse ((ELEM) =:= code)
+ orelse ((ELEM) =:= i) orelse ((ELEM) =:= br)
+ orelse ((ELEM) =:= em))).
+%% non-inline elements are:
+-define(BLOCK,[p,pre,ul,ol,li,dl,dt,dd,h1,h2,h3]).
+-define(IS_BLOCK(ELEM),not ?IS_INLINE(ELEM)).
+-define(IS_PRE(ELEM),(((ELEM) =:= pre))).
+
+-type chunk_element_type() :: a | p | i | br | em | pre | code | ul |
+ ol | li | dl | dt | dd.
+-type chunk_element_attr() :: {atom(),unicode:chardata()}.
+-type chunk_element_attrs() :: [chunk_element_attr()].
+-type chunk_element() :: {chunk_element_type(),chunk_element_attrs(),
+ chunk_elements()} | binary().
+-type chunk_elements() :: [chunk_element()].
+-type docs_v1() :: #docs_v1{}.
+
+
+-spec validate(Module) -> ok when
+ Module :: module() | docs_v1().
+%% Simple validation of erlang doc chunk. Check that all tags are supported and
+%% that the signature is correct.
+validate(Module) when is_atom(Module) ->
+ {ok, Doc} = code:get_doc(Module),
+ validate(Doc);
+validate(#docs_v1{ module_doc = MDocs, docs = AllDocs }) ->
+
+ %% Check some macro in-variants
+ AE = lists:sort(?ALL_ELEMENTS),
+ AE = lists:sort(?INLINE ++ ?BLOCK),
+ true = lists:all(fun(Elem) -> ?IS_INLINE(Elem) end, ?INLINE),
+ true = lists:all(fun(Elem) -> ?IS_BLOCK(Elem) end, ?BLOCK),
+
+ _ = maps:map(fun(_Key,MDoc) -> validate(MDoc) end, MDocs),
+ lists:map(fun({_,_Anno, Sig, Docs, _Meta}) ->
+ case lists:all(fun erlang:is_binary/1, Sig) of
+ false -> throw({invalid_signature,Sig});
+ true -> ok
+ end,
+ maps:map(fun(_Key,Doc) -> validate(Doc) end, Docs)
+ end, AllDocs);
+validate([H|T]) when is_tuple(H) ->
+ _ = validate(H),
+ validate(T);
+validate({Tag,Attr,Content}) ->
+ case lists:member(Tag,?ALL_ELEMENTS) of
+ false ->
+ throw({invalid_tag,Tag});
+ true ->
+ ok
+ end,
+ true = is_list(Attr),
+ validate(Content);
+validate([Chars | T]) when is_binary(Chars) ->
+ validate(T);
+validate([]) ->
+ ok.
+
+%% Follows algorithm described here:
+%% * https://medium.com/@patrickbrosset/when-does-white-space-matter-in-html-b90e8a7cdd33
+%% which in turn follows this:
+%% * https://www.w3.org/TR/css-text-3/#white-space-processing
+-spec normalize(Docs) -> NormalizedDocs when
+ Docs :: chunk_elements(),
+ NormalizedDocs :: chunk_elements().
+normalize(Docs) ->
+ Trimmed = normalize_trim(Docs,true),
+ normalize_space(Trimmed).
+
+normalize_trim(Bin,true) when is_binary(Bin) ->
+ %% Remove any whitespace (except \n) before or after a newline
+ NoSpace = re:replace(Bin,"[^\\S\n]*\n+[^\\S\n]*","\n",[global]),
+ %% Replace any tabs with space
+ NoTab = re:replace(NoSpace,"\t"," ",[global]),
+ %% Replace any newlines with space
+ NoNewLine = re:replace(NoTab,"\\v"," ",[global]),
+ %% Replace any sequences of \s with a single " "
+ re:replace(NoNewLine,"\\s+"," ",[global,{return,binary}]);
+normalize_trim(Bin,false) when is_binary(Bin) ->
+ Bin;
+normalize_trim([{pre,Attr,Content}|T],Trim) ->
+ [{pre,Attr,normalize_trim(Content,false)} | normalize_trim(T,Trim)];
+normalize_trim([{Tag,Attr,Content}|T],Trim) ->
+ [{Tag,Attr,normalize_trim(Content,Trim)} | normalize_trim(T,Trim)];
+normalize_trim([<<>>|T],Trim) ->
+ normalize_trim(T,Trim);
+normalize_trim([B1,B2|T],Trim) when is_binary(B1),is_binary(B2) ->
+ normalize_trim([<<B1/binary,B2/binary>> | T],Trim);
+normalize_trim([H|T],Trim) ->
+ [normalize_trim(H,Trim) | normalize_trim(T,Trim)];
+normalize_trim([],_Trim) ->
+ [].
+
+%% We want to remove any duplicate spaces, even if they
+%% cross into other inline elements.
+%% For non-inline elements we just need to make sure that any
+%% leading or trailing spaces are stripped.
+normalize_space([{Pre,Attr,Content}|T]) when ?IS_PRE(Pre) ->
+ [{Pre,Attr,trim_first_and_last(Content,$\n)} | normalize_space(T)];
+normalize_space([{Block,Attr,Content}|T]) when ?IS_BLOCK(Block) ->
+ [{Block,Attr,trim_first_and_last(trim_inline(Content),$ )} | normalize_space(T)];
+normalize_space([E|T]) ->
+ [E|normalize_space(T)];
+normalize_space([]) ->
+ [].
+
+trim_inline(Content) ->
+ {NewContent,_} = trim_inline(Content,false),
+ NewContent.
+trim_inline([Bin|T],false) when is_binary(Bin) ->
+ LastElem = binary:at(Bin,byte_size(Bin)-1),
+ {NewT, NewState} = trim_inline(T,LastElem =:= $ ),
+ {[Bin | NewT],NewState};
+trim_inline([<<" ">>|T],true) ->
+ trim_inline(T,false);
+trim_inline([<<" ",Bin/binary>>|T],true) when is_binary(Bin) ->
+ trim_inline([Bin | T],false);
+trim_inline([Bin|T],true) when is_binary(Bin) ->
+ trim_inline([Bin|T],false);
+trim_inline([{Elem,Attr,Content}|T],TrimSpace) when ?IS_INLINE(Elem) ->
+ {NewContent,ContentTrimSpace} = trim_inline(Content,TrimSpace),
+ {NewT,TTrimSpace} = trim_inline(T,ContentTrimSpace),
+ {[{Elem,Attr,NewContent} | NewT], TTrimSpace};
+trim_inline([{Elem1,_A1,_C1} = B1,<<" ">>,{Elem2,_A2,_C2} = B2|T],TrimSpace)
+ when ?IS_BLOCK(Elem1),?IS_BLOCK(Elem2) ->
+ trim_inline([B1,B2|T],TrimSpace);
+trim_inline([{Elem,_Attr,_Content} = Block|T],_TrimSpace) when ?IS_BLOCK(Elem) ->
+ [NewBlock] = normalize_space([Block]),
+ {NewT,TTrimSpace} = trim_inline(T,false),
+ {[NewBlock | NewT], TTrimSpace};
+trim_inline([],TrimSpace) ->
+ {[],TrimSpace}.
+
+
+%% This function removes the first and last What from the content.
+%% This is complicated by the fact that the first or last element
+%% may not have any binary, or have the binary deeply nested within.
+trim_first_and_last(Content, What) when What < 256 ->
+ {NewContent,_State} = trim_last(trim_first(Content,What),What),
+ NewContent.
+
+trim_first(Content,What) ->
+ {NewContent,_State} = trim_first(Content,false,What),
+ NewContent.
+trim_first([Bin|T],false,What) when is_binary(Bin) ->
+ case Bin of
+ <<What>> ->
+ {T,true};
+ <<What,NewBin/binary>> ->
+ {[NewBin|T],true};
+ Bin ->
+ {[Bin|T],true}
+ end;
+trim_first([{Elem,Attr,Content} = Tag|T],false,What) ->
+ case trim_first(Content,false,What) of
+ {NewContent,true} ->
+ {[{Elem,Attr,NewContent}|T],true};
+ {Content,false} ->
+ {NewT,NewState} = trim_first(T,false,What),
+ {[Tag | NewT],NewState}
+ end;
+trim_first([],false,_What) ->
+ {[],false}.
+
+trim_last([Bin | T],What) when is_binary(Bin) ->
+ case trim_last(T,What) of
+ {NewT,true} ->
+ {[Bin | NewT],true};
+ {T,false} ->
+ PreSz = byte_size(Bin)-1,
+ case Bin of
+ <<What>> -> {T,true};
+ <<NewBin:PreSz/binary,What>> ->
+ {[NewBin|T],true};
+ Bin ->
+ {[Bin|T],true}
+ end
+ end;
+trim_last([{Elem,Attr,Content} = Tag|T],What) ->
+ case trim_last(T,What) of
+ {NewT,true} ->
+ {[Tag | NewT],true};
+ {T,false} ->
+ {NewContent,NewState} = trim_last(Content,What),
+ {[{Elem,Attr,NewContent}|T],NewState}
+ end;
+trim_last([],_What) ->
+ {[],false}.
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% API function for dealing with the function documentation
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+-spec get_doc(Module :: module()) -> chunk_elements().
+get_doc(Module) ->
+ {ok, #docs_v1{ module_doc = ModuleDoc } } = code:get_doc(Module),
+ get_local_doc(Module, ModuleDoc).
+
+-spec get_doc(Module :: module(), Function, Arity) ->
+ [{{Function,Arity}, Anno, Signature, chunk_elements(), Metadata}] when
+ Function :: function(),
+ Arity :: arity(),
+ Anno :: erl_anno:anno(),
+ Signature :: [binary()],
+ Metadata :: #{}.
+get_doc(Module, Function, Arity) ->
+ {ok, #docs_v1{ docs = Docs } } = code:get_doc(Module),
+ FnFunctions =
+ lists:filter(fun({{function, F, A},_Anno,_Sig,_Doc,_Meta}) ->
+ F =:= Function andalso A =:= Arity;
+ (_) ->
+ false
+ end, Docs),
+
+ [{F,A,S,get_local_doc({F,A},D),M} || {F,A,S,D,M} <- FnFunctions].
+
+-spec render(Module :: module(), Docs :: docs_v1()) -> unicode:chardata().
+render(Module, #docs_v1{ module_doc = ModuleDoc, metadata = MD } = D) ->
+ render_docs([["\t",atom_to_binary(Module)]],
+ get_local_doc(Module, ModuleDoc), MD, D).
+
+-spec render(Module :: module(), Function :: function(), Docs :: docs_v1()) ->
+ unicode:chardata() | {error,function_missing}.
+render(_Module, Function, #docs_v1{ docs = Docs } = D) ->
+ render_function(
+ lists:filter(fun({{function, F, _},_Anno,_Sig,_Doc,_Meta}) ->
+ F =:= Function;
+ (_) ->
+ false
+ end, Docs), D).
+-spec render(Module :: module(), Function :: function(), Arity :: arity(),
+ Docs :: docs_v1()) -> unicode:chardata() | {error,function_missing}.
+render(_Module, Function, Arity, #docs_v1{ docs = Docs } = D) ->
+ render_function(
+ lists:filter(fun({{function, F, A},_Anno,_Sig,_Doc,_Meta}) ->
+ F =:= Function andalso A =:= Arity;
+ (_) ->
+ false
+ end, Docs), D).
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% API function for dealing with the type documentation
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+-spec get_type_doc(Module :: module(), Type :: atom(), Arity :: arity()) ->
+ [{{Type,Arity}, Anno, Signature, chunk_elements(), Metadata}] when
+ Type :: atom(),
+ Arity :: arity(),
+ Anno :: erl_anno:anno(),
+ Signature :: [binary()],
+ Metadata :: #{}.
+get_type_doc(Module, Type, Arity) ->
+ {ok, #docs_v1{ docs = Docs } } = code:get_doc(Module),
+ FnFunctions =
+ lists:filter(fun({{type, T, A},_Anno,_Sig,_Doc,_Meta}) ->
+ T =:= Type andalso A =:= Arity;
+ (_) ->
+ false
+ end, Docs),
+ [{F,A,S,get_local_doc(F, D),M} || {F,A,S,D,M} <- FnFunctions].
+
+-spec render_type(Module :: module(), Docs :: docs_v1()) -> unicode:chardata().
+render_type(Module, #docs_v1{ docs = Docs } = D) ->
+ render_type_signatures(Module,
+ lists:filter(fun({{type, _, _},_Anno,_Sig,_Doc,_Meta}) ->
+ true;
+ (_) ->
+ false
+ end, Docs), D).
+
+-spec render_type(Module :: module(), Type :: atom(), Docs :: docs_v1()) ->
+ unicode:chardata() | {error,type_missing}.
+render_type(_Module, Type, #docs_v1{ docs = Docs } = D) ->
+ render_type_docs(
+ lists:filter(fun({{type, T, _},_Anno,_Sig,_Doc,_Meta}) ->
+ T =:= Type;
+ (_) ->
+ false
+ end, Docs), D).
+
+-spec render_type(Module :: module(), Type :: atom(), Arity :: arity(),
+ Docs :: docs_v1()) -> unicode:chardata() | {error,type_missing}.
+render_type(_Module, Type, Arity, #docs_v1{ docs = Docs } = D) ->
+ render_type_docs(
+ lists:filter(fun({{type, T, A},_Anno,_Sig,_Doc,_Meta}) ->
+ T =:= Type andalso A =:= Arity;
+ (_) ->
+ false
+ end, Docs), D).
+
+
+%% Get the docs in the correct locale if it exists.
+get_local_doc(MissingMod, Docs) when is_atom(MissingMod) ->
+ get_local_doc(atom_to_binary(MissingMod), Docs);
+get_local_doc({F,A}, Docs) ->
+ get_local_doc(unicode:characters_to_binary(io_lib:format("~tp/~p",[F,A])), Docs);
+get_local_doc(_Missing, #{ <<"en">> := Docs }) ->
+ %% English if it exists
+ normalize(Docs);
+get_local_doc(_Missing, ModuleDoc) when map_size(ModuleDoc) > 0 ->
+ %% Otherwise take first alternative found
+ normalize(maps:get(hd(maps:keys(ModuleDoc)), ModuleDoc));
+get_local_doc(Missing, hidden) ->
+ [{p,[],[<<"The documentation for ">>,Missing,
+ <<" is hidden. This probably means that it is internal "
+ "and not to be used by other applications.">>]}];
+get_local_doc(Missing, None) when None =:= none; None =:= #{} ->
+ [{p,[],[<<"There is no documentation for ">>,Missing]}].
+
+%%% Functions for rendering reference documentation
+render_function([], _D) ->
+ {error,function_missing};
+render_function(FDocs, D) ->
+ [render_docs(render_signature(Func), get_local_doc({F,A},Doc), Meta, D)
+ || {{_,F,A},_Anno,_Sig,Doc,Meta} = Func <- lists:sort(FDocs)].
+
+%% Render the signature of either function or a type, or anything else really.
+render_signature({{_Type,_F,_A},_Anno,_Sig,_Docs,#{ signature := Specs }}) ->
+ [erl_pp:attribute(Spec,[{encoding,utf8}]) || Spec <- Specs];
+render_signature({{_Type,_F,_A},_Anno,Sigs,_Docs,_Meta}) ->
+ [Sig || Sig <- Sigs].
+
+render_since(#{ since := Vsn }) ->
+ ["\n\nSince: ",Vsn];
+render_since(_) ->
+ [].
+
+render_docs(Headers, DocContents, MD, D = #config{}) ->
+ init_ansi(D),
+ try
+ {Doc,_} = render_docs(DocContents,[],0,2,D),
+ [sansi(bold),
+ [io_lib:format("~n~ts",[Header]) || Header <- Headers],
+ ransi(bold),
+ render_since(MD),
+ io_lib:format("~n~n~ts",[Doc])]
+ after
+ clean_ansi()
+ end;
+render_docs(Headers, DocContents, MD, D) ->
+ render_docs(Headers, DocContents, MD, #config{ docs = D }).
+
+%%% Functions for rendering type documentation
+render_type_signatures(Module, Types, D = #config{}) ->
+ init_ansi(D),
+ try
+ [sansi(bold),"\t",atom_to_list(Module),ransi(bold),"\n\n",
+ [render_signature(Type) || Type <- Types ]]
+ after
+ clean_ansi()
+ end;
+render_type_signatures(Module, Types, D) ->
+ render_type_signatures(Module, Types, #config{ docs = D }).
+
+render_type_docs([], _D) ->
+ {error,type_missing};
+render_type_docs(Types, #config{} = D) when is_list(Types) ->
+ [render_type_docs(Type, D) || Type <- Types];
+render_type_docs({{_,F,A},_,_Sig,Docs,Meta} = Type, #config{} = D) ->
+ render_docs(render_signature(Type), get_local_doc({F,A},Docs), Meta, D);
+render_type_docs(Docs, D) ->
+ render_type_docs(Docs, #config{ docs = D }).
+
+%%% General rendering functions
+render_docs(Elems,State,Pos,Ind,D) when is_list(Elems) ->
+ lists:mapfoldl(fun(Elem,P) ->
+% io:format("Elem: ~p (~p) (~p,~p)~n",[Elem,State,P,Ind]),
+ render_docs(Elem,State,P,Ind,D)
+ end,Pos,Elems);
+render_docs(Elem,State,Pos,Ind,D) ->
+ render_element(Elem,State,Pos,Ind,D).
+
+
+%%% The function is the main element rendering function
+%%%
+%%% Elem: The current element to process
+%%% Stack: A stack of element names to see where we are in the dom
+%%% Pos: The current print position on the current line
+%%% Ind: How much the text should be indented after a newline
+%%% Config: The renderer's configuration
+%%%
+%%% Each element is responsible for putting new lines AFTER itself
+%%% The indents are done either by render_words when a newline happens
+%%% or when a new element is to be rendered and Pos < Ind.
+%%%
+%%% Any block elements (i.e. p, ul, li etc) are responsible for trimming
+%%% extra new lines. eg. <ul><li><p>content</p></li></ul> should only
+%%% have two newlines at the end.
+-spec render_element(Elem :: chunk_element(),
+ Stack :: [chunk_element_type()],
+ Pos :: non_neg_integer(),
+ Indent :: non_neg_integer(),
+ Config :: #config{}) ->
+ {unicode:chardata(), Pos :: non_neg_integer()}.
+
+render_element({IgnoreMe,_,Content}, State, Pos, Ind,D)
+ when IgnoreMe =:= a; IgnoreMe =:= anno ->
+ render_docs(Content, State, Pos, Ind,D);
+
+%% Catch h1, h2 and h3 before the padding is done as there reset padding
+render_element({h1,_,Content},State,0 = Pos,_Ind,D) ->
+ trimnlnl(render_element({code,[],[{em,[],Content}]}, State, Pos, 0, D));
+render_element({h2,_,Content},State,0 = Pos,_Ind,D) ->
+ trimnlnl(render_element({em,[],Content}, State, Pos, 0, D));
+render_element({h3,_,Content},State,Pos,_Ind,D) when Pos =< 2 ->
+ trimnlnl(render_element({code,[],Content}, State, Pos, 2, D));
+
+render_element({p,_Attr,_Content} = E,State,Pos,Ind,D) when Pos > Ind ->
+ {Docs,NewPos} = render_element(E,State,0,Ind,D),
+ {["\n",Docs],NewPos};
+render_element({p,[{class,What}],Content},State,Pos,Ind,D) ->
+ {Docs,_} = render_docs(Content, [p|State], 0, Ind+2, D),
+ trimnlnl([pad(Ind - Pos),string:titlecase(What),":\n",Docs]);
+render_element({p,_,Content},State,Pos,Ind,D) ->
+ trimnlnl(render_docs(Content, [p|State], Pos, Ind,D));
+
+render_element(Elem,State,Pos,Ind,D) when Pos < Ind ->
+% io:format("Pad: ~p~n",[Ind - Pos]),
+ {Docs,NewPos} = render_element(Elem,State,Ind,Ind,D),
+
+ {[pad(Ind - Pos), Docs],NewPos};
+
+render_element({code,_,Content},[pre|_] = State,Pos,Ind,D) ->
+ %% When code is within a pre we don't emit any underline
+ render_docs(Content, [code|State], Pos, Ind,D);
+render_element({code,_,Content},State,Pos,Ind,D) ->
+ Underline = sansi(underline),
+ {Docs, NewPos} = render_docs(Content, [code|State], Pos, Ind,D),
+ {[Underline,Docs,ransi(underline)], NewPos};
+
+render_element({i,_,Content},State,Pos,Ind,D) ->
+ %% Just ignore i as ansi does not have cursive style
+ render_docs(Content, State, Pos, Ind,D);
+
+render_element({br,[],[]},_State,_Pos,_Ind,_D) ->
+ nl("");
+
+render_element({em,_,Content},State,Pos,Ind,D) ->
+ Bold = sansi(bold),
+ {Docs, NewPos} = render_docs(Content, State, Pos, Ind,D),
+ {[Bold,Docs,ransi(bold)], NewPos};
+
+render_element({pre,_,Content},State,Pos,Ind,D) ->
+ %% For pre we make sure to respect the newlines in pre
+ trimnlnl(render_docs(Content, [pre|State], Pos, Ind+2, D));
+
+render_element({ul,[{class,"types"}],Content},State,_Pos,Ind,D) ->
+ {Docs, _} = render_docs(Content, [types|State], 0, Ind+2, D),
+ trimnlnl(["Types:\n", Docs]);
+render_element({li,Attr,Content},[types|_] = State,Pos,Ind,C) ->
+ Doc =
+ case {proplists:get_value(name, Attr),proplists:get_value(class, Attr)} of
+ {undefined,Class} when Class =:= undefined; Class =:= "type" ->
+ %% Inline html for types
+ render_docs(Content,[type|State],Pos,Ind,C);
+ {_,"description"} ->
+ %% Inline html for type descriptions
+ render_docs(Content,[type|State],Pos,Ind+2,C);
+ {Name,_} ->
+ %% Try to render from type metadata
+ case render_type_signature(list_to_atom(Name),C) of
+ undefined when Content =:= [] ->
+ %% Failed and no content, emit place-holder
+ {["-type ",Name,"() :: term()."],0};
+ undefined ->
+ %% Failed with metadata, render the content
+ render_docs(Content,[type|State],Pos,Ind,C);
+ Type ->
+ %% Emit the erl_pp typespec
+ {Type,0}
+ end
+ end,
+ trimnl(Doc);
+render_element({ul,[],Content},State,Pos,Ind,D) ->
+ render_docs(Content, [l|State], Pos, Ind,D);
+render_element({ol,[],Content},State,Pos,Ind,D) ->
+ %% For now ul and ol does the same thing
+ render_docs(Content, [l|State], Pos, Ind,D);
+render_element({li,[],Content},[l | _] = State, Pos, Ind,D) ->
+ Bullet = get_bullet(State, proplists:get_value(encoding, D#config.io_opts)),
+ BulletLen = string:length(Bullet),
+ {Docs, _NewPos} = render_docs(Content, [li | State], Pos + BulletLen,Ind + BulletLen, D),
+ trimnlnl([Bullet,Docs]);
+
+render_element({dl,_,Content},State,Pos,Ind,D) ->
+ render_docs(Content, [dl|State], Pos, Ind,D);
+render_element({dt,_,Content},[dl | _] = State,Pos,Ind,D) ->
+ Underline = sansi(underline),
+ {Docs, _NewPos} = render_docs(Content, [li | State], Pos, Ind, D),
+ {[Underline,Docs,ransi(underline),":","\n"], 0};
+render_element({dd,_,Content},[dl | _] = State,Pos,Ind,D) ->
+ trimnlnl(render_docs(Content, [li | State], Pos, Ind + 2, D));
+
+render_element(B, State, Pos, Ind,#config{ io_columns = Cols }) when is_binary(B) ->
+ case lists:member(pre,State) of
+ true ->
+ Pre = string:replace(B,"\n",["\n",pad(Ind)],all),
+ {Pre, Pos + lastline(Pre)};
+ _ ->
+ render_words(split_to_words(B),State,Pos,Ind,[[]],Cols)
+ end;
+
+render_element({Tag,Attr,Content}, State, Pos, Ind,D) ->
+ throw({unhandled,{Tag,Attr,Content,Pos,Ind}}),
+ render_docs(Content, State, Pos, Ind,D).
+
+render_words(Words,[_,types|State],Pos,Ind,Acc,Cols) ->
+ %% When we render words and are in the types->type state we indent
+ %% the extra lines two additional spaces to make it look nice
+ render_words(Words,State,Pos,Ind+2,Acc,Cols);
+render_words([Word|T],State,Pos,Ind,Acc,Cols) when is_binary(Word) ->
+ WordLength = string:length(Word),
+ NewPos = WordLength + Pos,
+ if
+ NewPos > (Cols - 10 - Ind) ->
+ %% Word does not fit, time to add a newline and also pad to Indent level
+ render_words(T,State,WordLength+Ind+1,Ind,[[[pad(Ind), Word]]|Acc],Cols);
+ true ->
+ %% Word does fit on line
+ [Line | LineAcc] = Acc,
+ %% Add + 1 to length for space
+ NewPosSpc = NewPos+1,
+ render_words(T,State,NewPosSpc,Ind,[[Word|Line]|LineAcc],Cols)
+ end;
+render_words([],_State,Pos,_Ind,Acc,_Cols) ->
+ Lines = lists:join(
+ $\n,lists:map(fun(RevLine) ->
+ Line = lists:reverse(RevLine),
+ lists:join($ ,Line)
+ end,lists:reverse(Acc))),
+ {iolist_to_binary(Lines), Pos}.
+
+render_type_signature(Name, #config{ docs = #docs_v1{ metadata = #{ types := AllTypes }}}) ->
+ case [Type || Type = {TName,_} <- maps:keys(AllTypes), TName =:= Name] of
+ [] ->
+ undefined;
+ Types ->
+ [erl_pp:attribute(maps:get(Type, AllTypes)) || Type <- Types]
+ end.
+
+%% Pad N spaces, disabling any ansi formatting while doing so
+pad(N) ->
+ Pad = lists:duplicate(N," "),
+ case ansi() of
+ undefined ->
+ Pad;
+ Ansi ->
+ ["\033[0m",Pad,Ansi]
+ end.
+
+get_bullet(_State,latin1) ->
+ <<" * ">>;
+get_bullet(State,unicode) ->
+ %% Fancy bullet point logic!
+ lists:nth(length([l || l <- State]),
+ [<<" • "/utf8>>,<<" ○ "/utf8>>,
+ <<" ◼ "/utf8>>,<<" ◻ "/utf8>>]).
+
+% Look for the length of the last line of a string
+lastline(Str) ->
+ LastStr = case string:find(Str,"\n",trailing) of
+ nomatch ->
+ Str;
+ Match ->
+ tl(string:next_codepoint(Match))
+ end,
+ string:length(LastStr).
+
+split_to_words(B) ->
+ binary:split(B,[<<" ">>],[global]).
+
+%% These functions make sure that we trim extra newlines added
+%% by the renderer. For example if we do <li><p></p></li>
+%% that would add 4 \n at after the last </li>. This is trimmed
+%% here to only be 2 \n
+trimnlnl({Chars, _Pos}) ->
+ nl(nl(string:trim(Chars, trailing, "\n")));
+trimnlnl(Chars) ->
+ nl(nl(string:trim(Chars, trailing, "\n"))).
+trimnl({Chars, _Pos}) ->
+ nl(string:trim(Chars, trailing, "\n")).
+nl({Chars, _Pos}) ->
+ nl(Chars);
+nl(Chars) ->
+ {[Chars,"\n"],0}.
+
+%% We keep the current ansi state in the pdict so that we know
+%% what to disable and enable when doing padding
+init_ansi(#config{ io_opts = Opts }) ->
+ %% We use this as our heuristic to see if we should print ansi or not
+ case {application:get_env(kernel, shell_docs_ansi),
+ proplists:is_defined(echo, Opts) andalso
+ proplists:is_defined(expand_fun, Opts),
+ os:type()} of
+ {{ok,false}, _, _} ->
+ put(ansi, noansi);
+ {{ok,true}, _, _} ->
+ put(ansi, []);
+ {_, _, {win32,_}} ->
+ put(ansi, noansi);
+ {_, true,_} ->
+ put(ansi, []);
+ {_, false,_} ->
+ put(ansi, noansi)
+ end.
+
+clean_ansi() ->
+ case get(ansi) of
+ [] -> erase(ansi);
+ noansi -> erase(ansi)
+ end,
+ ok.
+
+%% Set ansi
+sansi(Type) -> sansi(Type, get(ansi)).
+sansi(_Type, noansi) ->
+ [];
+sansi(Type, Curr) ->
+ put(ansi,[Type | Curr]),
+ ansi(get(ansi)).
+
+%% Clear ansi
+ransi(Type) -> ransi(Type, get(ansi)).
+ransi(_Type, noansi) ->
+ [];
+ransi(Type, Curr) ->
+ put(ansi,proplists:delete(Type,Curr)),
+ case ansi(get(ansi)) of
+ undefined ->
+ "\033[0m";
+ Ansi ->
+ Ansi
+ end.
+
+ansi() -> ansi(get(ansi)).
+ansi(noansi) -> undefined;
+ansi(Curr) ->
+ case lists:usort(Curr) of
+ [] ->
+ undefined;
+ [bold] ->
+ "\033[;1m";
+ [underline] ->
+ "\033[;;4m";
+ [bold,underline] ->
+ "\033[;1;4m"
+ end.
diff --git a/lib/stdlib/src/stdlib.app.src b/lib/stdlib/src/stdlib.app.src
index 6ade386159..9334a06ca2 100644
--- a/lib/stdlib/src/stdlib.app.src
+++ b/lib/stdlib/src/stdlib.app.src
@@ -92,6 +92,7 @@
sets,
shell,
shell_default,
+ shell_docs,
slave,
sofs,
string,
@@ -108,6 +109,6 @@
dets]},
{applications, [kernel]},
{env, []},
- {runtime_dependencies, ["sasl-3.0","kernel-6.0","erts-10.6.2","crypto-3.3",
+ {runtime_dependencies, ["sasl-3.0","kernel-@OTP-15251@","erts-@OTP-15251@","crypto-3.3",
"compiler-5.0"]}
]}.
diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl
index 1ac7334830..acb9dd1970 100644
--- a/lib/stdlib/src/supervisor.erl
+++ b/lib/stdlib/src/supervisor.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2018. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2019. 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.
@@ -32,6 +32,9 @@
-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
terminate/2, code_change/3, format_status/2]).
+%% logger callback
+-export([format_log/1, format_log/2]).
+
%% For release_handler only
-export([get_callback_module/1]).
@@ -44,14 +47,17 @@
{reason,Reason},
{offender,extract_child(Child)}]},
#{domain=>[otp,sasl],
- report_cb=>fun logger:format_otp_report/1,
+ report_cb=>fun supervisor:format_log/2,
logger_formatter=>#{title=>"SUPERVISOR REPORT"},
error_logger=>#{tag=>error_report,
- type=>supervisor_report}})).
+ type=>supervisor_report,
+ report_cb=>fun supervisor:format_log/1}})).
%%--------------------------------------------------------------------------
--export_type([sup_flags/0, child_spec/0, startchild_ret/0, strategy/0]).
+-export_type([sup_flags/0, child_spec/0, strategy/0,
+ startchild_ret/0, startchild_err/0,
+ startlink_ret/0, startlink_err/0]).
%%--------------------------------------------------------------------------
@@ -122,7 +128,7 @@
strategy :: strategy() | 'undefined',
children = {[],#{}} :: children(), % Ids in start order
dynamics :: {'maps', #{pid() => list()}}
- | {'sets', sets:set(pid())}
+ | {'mapsets', #{pid() => []}}
| 'undefined',
intensity :: non_neg_integer() | 'undefined',
period :: pos_integer() | 'undefined',
@@ -924,21 +930,21 @@ monitor_child(Pid) ->
terminate_dynamic_children(State) ->
Child = get_dynamic_child(State),
{Pids, EStack0} = monitor_dynamic_children(Child,State),
- Sz = sets:size(Pids),
+ Sz = maps:size(Pids),
EStack = case Child#child.shutdown of
brutal_kill ->
- sets:fold(fun(P, _) -> exit(P, kill) end, ok, Pids),
+ maps:fold(fun(P, _, _) -> exit(P, kill) end, ok, Pids),
wait_dynamic_children(Child, Pids, Sz, undefined, EStack0);
infinity ->
- sets:fold(fun(P, _) -> exit(P, shutdown) end, ok, Pids),
+ maps:fold(fun(P, _, _) -> exit(P, shutdown) end, ok, Pids),
wait_dynamic_children(Child, Pids, Sz, undefined, EStack0);
Time ->
- sets:fold(fun(P, _) -> exit(P, shutdown) end, ok, Pids),
+ maps:fold(fun(P, _, _) -> exit(P, shutdown) end, ok, Pids),
TRef = erlang:start_timer(Time, self(), kill),
wait_dynamic_children(Child, Pids, Sz, TRef, EStack0)
end,
%% Unroll stacked errors and report them
- dict:fold(fun(Reason, Ls, _) ->
+ maps:fold(fun(Reason, Ls, _) ->
?report_error(shutdown_error, Reason,
Child#child{pid=Ls}, State#state.name)
end, ok, EStack).
@@ -947,15 +953,15 @@ monitor_dynamic_children(Child,State) ->
dyn_fold(fun(P,{Pids, EStack}) when is_pid(P) ->
case monitor_child(P) of
ok ->
- {sets:add_element(P, Pids), EStack};
+ {maps:put(P, P, Pids), EStack};
{error, normal} when not (?is_permanent(Child)) ->
{Pids, EStack};
{error, Reason} ->
- {Pids, dict:append(Reason, P, EStack)}
+ {Pids, maps_prepend(Reason, P, EStack)}
end;
(?restarting(_), {Pids, EStack}) ->
{Pids, EStack}
- end, {sets:new(), dict:new()}, State).
+ end, {maps:new(), maps:new()}, State).
wait_dynamic_children(_Child, _Pids, 0, undefined, EStack) ->
EStack;
@@ -973,36 +979,44 @@ wait_dynamic_children(#child{shutdown=brutal_kill} = Child, Pids, Sz,
TRef, EStack) ->
receive
{'DOWN', _MRef, process, Pid, killed} ->
- wait_dynamic_children(Child, sets:del_element(Pid, Pids), Sz-1,
+ wait_dynamic_children(Child, maps:remove(Pid, Pids), Sz-1,
TRef, EStack);
{'DOWN', _MRef, process, Pid, Reason} ->
- wait_dynamic_children(Child, sets:del_element(Pid, Pids), Sz-1,
- TRef, dict:append(Reason, Pid, EStack))
+ wait_dynamic_children(Child, maps:remove(Pid, Pids), Sz-1,
+ TRef, maps_prepend(Reason, Pid, EStack))
end;
wait_dynamic_children(Child, Pids, Sz, TRef, EStack) ->
receive
{'DOWN', _MRef, process, Pid, shutdown} ->
- wait_dynamic_children(Child, sets:del_element(Pid, Pids), Sz-1,
+ wait_dynamic_children(Child, maps:remove(Pid, Pids), Sz-1,
TRef, EStack);
{'DOWN', _MRef, process, Pid, {shutdown, _}} ->
- wait_dynamic_children(Child, sets:del_element(Pid, Pids), Sz-1,
+ wait_dynamic_children(Child, maps:remove(Pid, Pids), Sz-1,
TRef, EStack);
{'DOWN', _MRef, process, Pid, normal} when not (?is_permanent(Child)) ->
- wait_dynamic_children(Child, sets:del_element(Pid, Pids), Sz-1,
+ wait_dynamic_children(Child, maps:remove(Pid, Pids), Sz-1,
TRef, EStack);
{'DOWN', _MRef, process, Pid, Reason} ->
- wait_dynamic_children(Child, sets:del_element(Pid, Pids), Sz-1,
- TRef, dict:append(Reason, Pid, EStack));
+ wait_dynamic_children(Child, maps:remove(Pid, Pids), Sz-1,
+ TRef, maps_prepend(Reason, Pid, EStack));
{timeout, TRef, kill} ->
- sets:fold(fun(P, _) -> exit(P, kill) end, ok, Pids),
+ maps:fold(fun(P, _, _) -> exit(P, kill) end, ok, Pids),
wait_dynamic_children(Child, Pids, Sz, undefined, EStack)
end.
+maps_prepend(Key, Value, Map) ->
+ case maps:find(Key, Map) of
+ {ok, Values} ->
+ maps:put(Key, [Value|Values], Map);
+ error ->
+ maps:put(Key, [Value], Map)
+ end.
+
%%-----------------------------------------------------------------
%% Access #state.children
%%-----------------------------------------------------------------
@@ -1420,9 +1434,159 @@ report_progress(Child, SupName) ->
report=>[{supervisor,SupName},
{started,extract_child(Child)}]},
#{domain=>[otp,sasl],
- report_cb=>fun logger:format_otp_report/1,
+ report_cb=>fun supervisor:format_log/2,
logger_formatter=>#{title=>"PROGRESS REPORT"},
- error_logger=>#{tag=>info_report,type=>progress}}).
+ error_logger=>#{tag=>info_report,
+ type=>progress,
+ report_cb=>fun supervisor:format_log/1}}).
+
+%% format_log/1 is the report callback used by Logger handler
+%% error_logger only. It is kept for backwards compatibility with
+%% legacy error_logger event handlers. This function must always
+%% return {Format,Args} compatible with the arguments in this module's
+%% calls to error_logger prior to OTP-21.0.
+format_log(LogReport) ->
+ Depth = error_logger:get_format_depth(),
+ FormatOpts = #{chars_limit => unlimited,
+ depth => Depth,
+ single_line => false,
+ encoding => utf8},
+ format_log_multi(limit_report(LogReport, Depth), FormatOpts).
+
+limit_report(LogReport, unlimited) ->
+ LogReport;
+limit_report(#{label:={supervisor,progress},
+ report:=[{supervisor,_}=Supervisor,{started,Child}]}=LogReport,
+ Depth) ->
+ LogReport#{report=>[Supervisor,
+ {started,limit_child_report(Child, Depth)}]};
+limit_report(#{label:={supervisor,_Error},
+ report:=[{supervisor,_}=Supervisor,{errorContext,Ctxt},
+ {reason,Reason},{offender,Child}]}=LogReport,
+ Depth) ->
+ LogReport#{report=>[Supervisor,
+ {errorContext,io_lib:limit_term(Ctxt, Depth)},
+ {reason,io_lib:limit_term(Reason, Depth)},
+ {offender,limit_child_report(Child, Depth)}]}.
+
+limit_child_report(Report, Depth) ->
+ io_lib:limit_term(Report, Depth).
+
+%% format_log/2 is the report callback for any Logger handler, except
+%% error_logger.
+format_log(Report, FormatOpts0) ->
+ Default = #{chars_limit => unlimited,
+ depth => unlimited,
+ single_line => false,
+ encoding => utf8},
+ FormatOpts = maps:merge(Default, FormatOpts0),
+ IoOpts =
+ case FormatOpts of
+ #{chars_limit:=unlimited} ->
+ [];
+ #{chars_limit:=Limit} ->
+ [{chars_limit,Limit}]
+ end,
+ {Format,Args} = format_log_single(Report, FormatOpts),
+ io_lib:format(Format, Args, IoOpts).
+
+format_log_single(#{label:={supervisor,progress},
+ report:=[{supervisor,SupName},{started,Child}]},
+ #{single_line:=true,depth:=Depth}=FormatOpts) ->
+ P = p(FormatOpts),
+ {ChildFormat,ChildArgs} = format_child_log_single(Child, "Started:"),
+ Format = "Supervisor: "++P++".",
+ Args =
+ case Depth of
+ unlimited ->
+ [SupName];
+ _ ->
+ [SupName,Depth]
+ end,
+ {Format++ChildFormat,Args++ChildArgs};
+format_log_single(#{label:={supervisor,_Error},
+ report:=[{supervisor,SupName},
+ {errorContext,Ctxt},
+ {reason,Reason},
+ {offender,Child}]},
+ #{single_line:=true,depth:=Depth}=FormatOpts) ->
+ P = p(FormatOpts),
+ Format = lists:append(["Supervisor: ",P,". Context: ",P,
+ ". Reason: ",P,"."]),
+ {ChildFormat,ChildArgs} = format_child_log_single(Child, "Offender:"),
+ Args =
+ case Depth of
+ unlimited ->
+ [SupName,Ctxt,Reason];
+ _ ->
+ [SupName,Depth,Ctxt,Depth,Reason,Depth]
+ end,
+ {Format++ChildFormat,Args++ChildArgs};
+format_log_single(Report,FormatOpts) ->
+ format_log_multi(Report,FormatOpts).
+
+format_log_multi(#{label:={supervisor,progress},
+ report:=[{supervisor,SupName},
+ {started,Child}]},
+ #{depth:=Depth}=FormatOpts) ->
+ P = p(FormatOpts),
+ Format =
+ lists:append(
+ [" supervisor: ",P,"~n",
+ " started: ",P,"~n"]),
+ Args =
+ case Depth of
+ unlimited ->
+ [SupName,Child];
+ _ ->
+ [SupName,Depth,Child,Depth]
+ end,
+ {Format,Args};
+format_log_multi(#{label:={supervisor,_Error},
+ report:=[{supervisor,SupName},
+ {errorContext,Ctxt},
+ {reason,Reason},
+ {offender,Child}]},
+ #{depth:=Depth}=FormatOpts) ->
+ P = p(FormatOpts),
+ Format =
+ lists:append(
+ [" supervisor: ",P,"~n",
+ " errorContext: ",P,"~n",
+ " reason: ",P,"~n",
+ " offender: ",P,"~n"]),
+ Args =
+ case Depth of
+ unlimited ->
+ [SupName,Ctxt,Reason,Child];
+ _ ->
+ [SupName,Depth,Ctxt,Depth,Reason,Depth,Child,Depth]
+ end,
+ {Format,Args}.
+
+format_child_log_single(Child, Tag) ->
+ {id,Id} = lists:keyfind(id, 1, Child),
+ case lists:keyfind(pid, 1, Child) of
+ false ->
+ {nb_children,NumCh} = lists:keyfind(nb_children, 1, Child),
+ {" ~s id=~w,nb_children=~w.", [Tag,Id,NumCh]};
+ T when is_tuple(T) ->
+ {pid,Pid} = lists:keyfind(pid, 1, Child),
+ {" ~s id=~w,pid=~w.", [Tag,Id,Pid]}
+ end.
+
+p(#{single_line:=Single,depth:=Depth,encoding:=Enc}) ->
+ "~"++single(Single)++mod(Enc)++p(Depth);
+p(unlimited) ->
+ "p";
+p(_Depth) ->
+ "P".
+
+single(true) -> "0";
+single(false) -> "".
+
+mod(latin1) -> "";
+mod(_) -> "t".
format_status(terminate, [_PDict, State]) ->
State;
@@ -1431,36 +1595,41 @@ format_status(_, [_PDict, State]) ->
{supervisor, [{"Callback", State#state.module}]}].
%%%-----------------------------------------------------------------
-%%% Dynamics database access
-dyn_size(#state{dynamics = {Mod,Db}}) ->
- Mod:size(Db).
+%%% Dynamics database access.
+%%%
+%%% Store all dynamic children in a map with the pid as the key. If
+%%% the children are permanent, store the start arguments as the value,
+%%% otherwise store [] as the value.
+%%%
-dyn_erase(Pid,#state{dynamics={sets,Db}}=State) ->
- State#state{dynamics={sets,sets:del_element(Pid,Db)}};
-dyn_erase(Pid,#state{dynamics={maps,Db}}=State) ->
+dyn_size(#state{dynamics = {_Kind,Db}}) ->
+ map_size(Db).
+
+dyn_erase(Pid,#state{dynamics={_Kind,Db}}=State) ->
State#state{dynamics={maps,maps:remove(Pid,Db)}}.
-dyn_store(Pid,_,#state{dynamics={sets,Db}}=State) ->
- State#state{dynamics={sets,sets:add_element(Pid,Db)}};
-dyn_store(Pid,Args,#state{dynamics={maps,Db}}=State) ->
- State#state{dynamics={maps,Db#{Pid => Args}}}.
+dyn_store(Pid,Args,#state{dynamics={Kind,Db}}=State) ->
+ case Kind of
+ mapsets ->
+ %% Children are temporary. The start arguments
+ %% will not be needed again. Store [].
+ State#state{dynamics={mapsets,Db#{Pid => []}}};
+ maps ->
+ %% Children are permanent and may be restarted.
+ %% Store the start arguments.
+ State#state{dynamics={maps,Db#{Pid => Args}}}
+ end.
-dyn_fold(Fun,Init,#state{dynamics={sets,Db}}) ->
- sets:fold(Fun,Init,Db);
-dyn_fold(Fun,Init,#state{dynamics={maps,Db}}) ->
+dyn_fold(Fun,Init,#state{dynamics={_Kind,Db}}) ->
maps:fold(fun(Pid,_,Acc) -> Fun(Pid,Acc) end, Init, Db).
-dyn_map(Fun, #state{dynamics={sets,Db}}) ->
- lists:map(Fun, sets:to_list(Db));
-dyn_map(Fun, #state{dynamics={maps,Db}}) ->
+dyn_map(Fun, #state{dynamics={_Kind,Db}}) ->
lists:map(Fun, maps:keys(Db)).
-dyn_exists(Pid, #state{dynamics={sets, Db}}) ->
- sets:is_element(Pid, Db);
-dyn_exists(Pid, #state{dynamics={maps, Db}}) ->
- maps:is_key(Pid, Db).
+dyn_exists(Pid, #state{dynamics={_Kind, Db}}) ->
+ is_map_key(Pid, Db).
-dyn_args(_Pid, #state{dynamics={sets, _Db}}) ->
+dyn_args(_Pid, #state{dynamics={mapsets, _Db}}) ->
{ok,undefined};
dyn_args(Pid, #state{dynamics={maps, Db}}) ->
maps:find(Pid, Db).
@@ -1469,6 +1638,6 @@ dyn_init(State) ->
dyn_init(get_dynamic_child(State),State).
dyn_init(Child,State) when ?is_temporary(Child) ->
- State#state{dynamics={sets,sets:new()}};
+ State#state{dynamics={mapsets,maps:new()}};
dyn_init(_Child,State) ->
State#state{dynamics={maps,maps:new()}}.
diff --git a/lib/stdlib/src/supervisor_bridge.erl b/lib/stdlib/src/supervisor_bridge.erl
index 21ba6f53af..abbfb404a5 100644
--- a/lib/stdlib/src/supervisor_bridge.erl
+++ b/lib/stdlib/src/supervisor_bridge.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2018. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2019. 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.
@@ -28,6 +28,8 @@
%% Internal exports
-export([init/1, handle_call/3, handle_cast/2, handle_info/2, terminate/2]).
-export([code_change/3]).
+%% logger callback
+-export([format_log/1, format_log/2]).
-callback init(Args :: term()) ->
{ok, Pid :: pid(), State :: term()} | ignore | {error, Error :: term()}.
@@ -136,9 +138,12 @@ report_progress(Pid, Mod, StartArgs, SupName) ->
{started, [{pid, Pid},
{mfa, {Mod, init, [StartArgs]}}]}]},
#{domain=>[otp,sasl],
- report_cb=>fun logger:format_otp_report/1,
+ report_cb=>fun supervisor_bridge:format_log/2,
logger_formatter=>#{title=>"PROGRESS REPORT"},
- error_logger=>#{tag=>info_report,type=>progress}}).
+ error_logger=>#{tag=>info_report,
+ type=>progress,
+ report_cb=>
+ fun supervisor_bridge:format_log/1}}).
report_error(Error, Reason, #state{name = Name, pid = Pid, mod = Mod}) ->
?LOG_ERROR(#{label=>{supervisor,error},
@@ -147,6 +152,167 @@ report_error(Error, Reason, #state{name = Name, pid = Pid, mod = Mod}) ->
{reason, Reason},
{offender, [{pid, Pid}, {mod, Mod}]}]},
#{domain=>[otp,sasl],
- report_cb=>fun logger:format_otp_report/1,
+ report_cb=>fun supervisor_bridge:format_log/2,
logger_formatter=>#{title=>"SUPERVISOR REPORT"},
- error_logger=>#{tag=>error_report,type=>supervisor_report}}).
+ error_logger=>#{tag=>error_report,
+ type=>supervisor_report,
+ report_cb=>
+ fun supervisor_bridge:format_log/1}}).
+
+%% format_log/1 is the report callback used by Logger handler
+%% error_logger only. It is kept for backwards compatibility with
+%% legacy error_logger event handlers. This function must always
+%% return {Format,Args} compatible with the arguments in this module's
+%% calls to error_logger prior to OTP-21.0.
+format_log(LogReport) ->
+ Depth = error_logger:get_format_depth(),
+ FormatOpts = #{chars_limit => unlimited,
+ depth => Depth,
+ single_line => false,
+ encoding => utf8},
+ format_log_multi(limit_report(LogReport, Depth), FormatOpts).
+
+limit_report(LogReport, unlimited) ->
+ LogReport;
+limit_report(#{label:={supervisor,progress},
+ report:=[{supervisor,_}=Supervisor,{started,Child}]}=LogReport,
+ Depth) ->
+ LogReport#{report=>[Supervisor,
+ {started,limit_child_report(Child, Depth)}]};
+limit_report(#{label:={supervisor,error},
+ report:=[{supervisor,_}=Supervisor,{errorContext,Ctxt},
+ {reason,Reason},{offender,Child}]}=LogReport,
+ Depth) ->
+ LogReport#{report=>[Supervisor,
+ {errorContext,io_lib:limit_term(Ctxt, Depth)},
+ {reason,io_lib:limit_term(Reason, Depth)},
+ {offender,io_lib:limit_term(Child, Depth)}]}.
+
+limit_child_report(ChildReport, Depth) ->
+ {mfa,{M,F,[As]}} = lists:keyfind(mfa, 1, ChildReport),
+ NewMFAs = {M,F,[io_lib:limit_term(As, Depth)]},
+ lists:keyreplace(mfa, 1, ChildReport, {mfa,NewMFAs}).
+
+%% format_log/2 is the report callback for any Logger handler, except
+%% error_logger.
+format_log(Report, FormatOpts0) ->
+ Default = #{chars_limit => unlimited,
+ depth => unlimited,
+ single_line => false,
+ encoding => utf8},
+ FormatOpts = maps:merge(Default, FormatOpts0),
+ IoOpts =
+ case FormatOpts of
+ #{chars_limit:=unlimited} ->
+ [];
+ #{chars_limit:=Limit} ->
+ [{chars_limit,Limit}]
+ end,
+ {Format,Args} = format_log_single(Report, FormatOpts),
+ io_lib:format(Format, Args, IoOpts).
+
+format_log_single(#{label:={supervisor,progress},
+ report:=[{supervisor,SupName},{started,Child}]},
+ #{single_line:=true,depth:=Depth}=FormatOpts) ->
+ P = p(FormatOpts),
+ {ChildFormat,ChildArgs} =
+ format_child_log_progress_single(Child, "Started:", FormatOpts),
+ Format = "Supervisor: "++P++".",
+ Args =
+ case Depth of
+ unlimited ->
+ [SupName];
+ _ ->
+ [SupName,Depth]
+ end,
+ {Format++ChildFormat,Args++ChildArgs};
+format_log_single(#{label:={supervisor,_Error},
+ report:=[{supervisor,SupName},
+ {errorContext,Ctxt},
+ {reason,Reason},
+ {offender,Child}]},
+ #{single_line:=true,depth:=Depth}=FormatOpts) ->
+ P = p(FormatOpts),
+ Format = lists:append(["Supervisor: ",P,". Context: ",P,
+ ". Reason: ",P,"."]),
+ {ChildFormat,ChildArgs} =
+ format_child_log_error_single(Child, "Offender:"),
+ Args =
+ case Depth of
+ unlimited ->
+ [SupName,Ctxt,Reason];
+ _ ->
+ [SupName,Depth,Ctxt,Depth,Reason,Depth]
+ end,
+ {Format++ChildFormat,Args++ChildArgs};
+format_log_single(Report, FormatOpts) ->
+ format_log_multi(Report, FormatOpts).
+
+format_log_multi(#{label:={supervisor,progress},
+ report:=[{supervisor,SupName},
+ {started,Child}]},
+ #{depth:=Depth}=FormatOpts) ->
+ P = p(FormatOpts),
+ Format =
+ lists:append(
+ [" supervisor: ",P,"~n",
+ " started: ",P,"~n"]),
+ Args =
+ case Depth of
+ unlimited ->
+ [SupName,Child];
+ _ ->
+ [SupName,Depth,Child,Depth]
+ end,
+ {Format,Args};
+format_log_multi(#{label:={supervisor,_Error},
+ report:=[{supervisor,SupName},
+ {errorContext,Ctxt},
+ {reason,Reason},
+ {offender,Child}]},
+ #{depth:=Depth}=FormatOpts) ->
+ P = p(FormatOpts),
+ Format =
+ lists:append(
+ [" supervisor: ",P,"~n",
+ " errorContext: ",P,"~n",
+ " reason: ",P,"~n",
+ " offender: ",P,"~n"]),
+ Args =
+ case Depth of
+ unlimited ->
+ [SupName,Ctxt,Reason,Child];
+ _ ->
+ [SupName,Depth,Ctxt,Depth,Reason,Depth,Child,Depth]
+ end,
+ {Format,Args}.
+
+format_child_log_progress_single(Child, Tag, FormatOpts) ->
+ {pid,Pid} = lists:keyfind(pid, 1, Child),
+ {mfa,MFAs} = lists:keyfind(mfa, 1, Child),
+ Args =
+ case maps:get(depth, FormatOpts) of
+ unlimited ->
+ [MFAs];
+ Depth ->
+ [MFAs, Depth]
+ end,
+ {" ~s pid=~w,mfa="++p(FormatOpts)++".",[Tag,Pid]++Args}.
+
+format_child_log_error_single(Child, Tag) ->
+ {pid,Pid} = lists:keyfind(pid, 1, Child),
+ {mod,Mod} = lists:keyfind(mod, 1, Child),
+ {" ~s pid=~w,mod=~w.",[Tag,Pid,Mod]}.
+
+p(#{single_line:=Single,depth:=Depth,encoding:=Enc}) ->
+ "~"++single(Single)++mod(Enc)++p(Depth);
+p(unlimited) ->
+ "p";
+p(_Depth) ->
+ "P".
+
+single(true) -> "0";
+single(false) -> "".
+
+mod(latin1) -> "";
+mod(_) -> "t".
diff --git a/lib/stdlib/src/sys.erl b/lib/stdlib/src/sys.erl
index 93bf4743d2..e803b749f7 100644
--- a/lib/stdlib/src/sys.erl
+++ b/lib/stdlib/src/sys.erl
@@ -31,7 +31,10 @@
install/2, install/3, remove/2, remove/3]).
-export([handle_system_msg/6, handle_system_msg/7, handle_debug/4,
print_log/1, get_log/1, get_debug/3, debug_options/1, suspend_loop_hib/6]).
--deprecated([{get_debug,3,eventually}]).
+
+-deprecated([{get_debug,3,
+ "incorrectly documented and only for internal use. Can often "
+ "be replaced with sys:get_log/1"}]).
%%-----------------------------------------------------------------
%% Types
diff --git a/lib/stdlib/src/zip.erl b/lib/stdlib/src/zip.erl
index a922bf3fbe..8f703d9d1a 100644
--- a/lib/stdlib/src/zip.erl
+++ b/lib/stdlib/src/zip.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2006-2018. All Rights Reserved.
+%% Copyright Ericsson AB 2006-2019. 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.
@@ -53,6 +53,10 @@
%% for debugging, to turn off catch
-define(CATCH, catch).
+%% Debug.
+-define(SHOW_GP_BIT_11(B, F), ok).
+%%-define(SHOW_GP_BIT_11(B, F), io:format("F = ~.16#, B = ~lp\n", [F, B])).
+
%% option sets
-record(unzip_opts, {
output, % output object (fun)
@@ -138,6 +142,10 @@
-define(PKWARE_RESERVED, 11).
-define(BZIP2_COMPRESSED, 12).
+%% Version 2.0, attribute compatibility type 3 (Unix)
+-define(VERSION_MADE_BY, 20 bor (3 bsl 8)).
+-define(GP_BIT_11, 16#800). % Filename and file comment UTF-8 encoded.
+
%% zip-file records
-define(LOCAL_FILE_MAGIC,16#04034b50).
-define(LOCAL_FILE_HEADER_SZ,(4+2+2+2+2+2+4+4+4+2+2)).
@@ -160,6 +168,7 @@
-define(CENTRAL_DIR_DIGITAL_SIG_MAGIC, 16#05054b50).
-define(CENTRAL_DIR_DIGITAL_SIG_SZ, (4+2)).
+-define(CENTRAL_FILE_EXT_ATTRIBUTES, 8#644 bsl 16).
-define(CENTRAL_FILE_MAGIC, 16#02014b50).
-record(cd_file_header, {version_made_by,
@@ -191,12 +200,16 @@
zip_comment_length}).
--type create_option() :: memory | cooked | verbose | {comment, string()}
- | {cwd, file:filename()}
- | {compress, extension_spec()}
- | {uncompress, extension_spec()}.
+-type create_option() :: memory | cooked | verbose
+ | {comment, Comment ::string()}
+ | {cwd, CWD :: file:filename()}
+ | {compress, What :: extension_spec()}
+ | {uncompress, What :: extension_spec()}.
-type extension() :: string().
--type extension_spec() :: all | [extension()] | {add, [extension()]} | {del, [extension()]}.
+-type extension_spec() :: all
+ | [Extension :: extension()]
+ | {add, [Extension :: extension()]}
+ | {del, [Extension :: extension()]}.
-type filename() :: file:filename().
-type zip_comment() :: #zip_comment{}.
@@ -277,8 +290,11 @@ do_openzip_get(_, _) ->
throw(einval).
file_name_search(Name,Files) ->
- case lists:dropwhile(fun({ZipFile,_}) -> ZipFile#zip_file.name =/= Name end,
- Files) of
+ Fun = fun({ZipFile,_}) ->
+ not string:equal(ZipFile#zip_file.name, Name,
+ _IgnoreCase = false, _Norm = nfc)
+ end,
+ case lists:dropwhile(Fun, Files) of
[ZFile|_] -> ZFile;
[] -> false
end.
@@ -429,12 +445,7 @@ zip(F, Files) -> zip(F, Files, []).
FileSpec :: file:name() | {file:name(), binary()}
| {file:name(), binary(), file:file_info()},
Options :: [Option],
- Option :: memory | cooked | verbose | {comment, Comment}
- | {cwd, CWD} | {compress, What} | {uncompress, What},
- What :: all | [Extension] | {add, [Extension]} | {del, [Extension]},
- Extension :: string(),
- Comment :: string(),
- CWD :: file:filename(),
+ Option :: create_option(),
RetValue :: {ok, FileName :: file:name()}
| {ok, {FileName :: file:name(), binary()}}
| {error, Reason :: term()}).
@@ -622,9 +633,11 @@ get_zip_opt([Unknown | _Rest], _Opts) ->
%% feedback funs
silent(_) -> ok.
-verbose_unzip(FN) -> io:format("extracting: ~tp\n", [FN]).
+verbose_unzip(FN) ->
+ io:format("extracting: ~ts\n", [io_lib:write_string(FN)]).
-verbose_zip(FN) -> io:format("adding: ~tp\n", [FN]).
+verbose_zip(FN) ->
+ io:format("adding: ~ts\n", [io_lib:write_string(FN)]).
%% file filter funs
all(_) -> true.
@@ -655,7 +668,10 @@ get_zip_options(Files, Options) ->
compress = all,
uncompress = Suffixes
},
- get_zip_opt(Options, Opts).
+ Opts1 = #zip_opts{comment = Comment} = get_zip_opt(Options, Opts),
+ %% UTF-8 encode characters in the interval from 127 to 255.
+ {Comment1, _} = encode_string(Comment),
+ Opts1#zip_opts{comment = Comment1}.
get_unzip_options(F, Options) ->
Opts = #unzip_opts{file_filter = fun all/1,
@@ -850,16 +866,18 @@ put_z_files([F | Rest], Z, Out0, Pos0,
regular -> FileInfo#file_info.size;
directory -> 0
end,
- FileName = get_filename(F, Type),
+ FileName0 = get_filename(F, Type),
+ %% UTF-8 encode characters in the interval from 127 to 255.
+ {FileName, GPFlag} = encode_string(FileName0),
CompMethod = get_comp_method(FileName, UncompSize, Opts, Type),
- LH = local_file_header_from_info_method_name(FileInfo, UncompSize, CompMethod, FileName),
+ LH = local_file_header_from_info_method_name(FileInfo, UncompSize, CompMethod, FileName, GPFlag),
BLH = local_file_header_to_bin(LH),
B = [<<?LOCAL_FILE_MAGIC:32/little>>, BLH],
Out1 = Output({write, B}, Out0),
Out2 = Output({write, FileName}, Out1),
{Out3, CompSize, CRC} = put_z_file(CompMethod, UncompSize, Out2, F1,
0, Input, Output, OpO, Z, Type),
- FB(FileName),
+ FB(FileName0),
Patch = <<CRC:32/little, CompSize:32/little>>,
Out4 = Output({pwrite, Pos0 + ?LOCAL_FILE_HEADER_CRC32_OFFSET, Patch}, Out3),
Out5 = Output({seek, eof, 0}, Out4),
@@ -1012,7 +1030,7 @@ cd_file_header_from_lh_and_pos(LH, Pos) ->
uncomp_size = UncompSize,
file_name_length = FileNameLength,
extra_field_length = ExtraFieldLength} = LH,
- #cd_file_header{version_made_by = 20,
+ #cd_file_header{version_made_by = ?VERSION_MADE_BY,
version_needed = VersionNeeded,
gp_flag = GPFlag,
comp_method = CompMethod,
@@ -1026,7 +1044,7 @@ cd_file_header_from_lh_and_pos(LH, Pos) ->
file_comment_length = 0, % FileCommentLength,
disk_num_start = 0, % DiskNumStart,
internal_attr = 0, % InternalAttr,
- external_attr = 0, % ExternalAttr,
+ external_attr = ?CENTRAL_FILE_EXT_ATTRIBUTES, % ExternalAttr,
local_header_offset = Pos}.
cd_file_header_to_bin(
@@ -1103,10 +1121,10 @@ eocd_to_bin(#eocd{disk_num = DiskNum,
%% put together a local file header
local_file_header_from_info_method_name(#file_info{mtime = MTime},
UncompSize,
- CompMethod, Name) ->
+ CompMethod, Name, GPFlag) ->
{ModDate, ModTime} = dos_date_time_from_datetime(MTime),
#local_file_header{version_needed = 20,
- gp_flag = 0,
+ gp_flag = GPFlag,
comp_method = CompMethod,
last_mod_time = ModTime,
last_mod_date = ModDate,
@@ -1270,7 +1288,9 @@ get_central_dir(In0, RawIterator, Input) ->
In2 = Input({seek, bof, EOCD#eocd.offset}, In1),
N = EOCD#eocd.entries,
Acc0 = [],
- Out0 = RawIterator(EOCD, "", binary_to_list(BComment), <<>>, Acc0),
+ %% There is no encoding flag for the archive comment.
+ Comment = heuristic_to_string(BComment),
+ Out0 = RawIterator(EOCD, "", Comment, <<>>, Acc0),
get_cd_loop(N, In2, RawIterator, Input, Out0).
get_cd_loop(0, In, _RawIterator, _Input, Acc) ->
@@ -1286,20 +1306,32 @@ get_cd_loop(N, In0, RawIterator, Input, Acc0) ->
ExtraLen = CD#cd_file_header.extra_field_length,
CommentLen = CD#cd_file_header.file_comment_length,
ToRead = FileNameLen + ExtraLen + CommentLen,
+ GPFlag = CD#cd_file_header.gp_flag,
{B2, In2} = Input({read, ToRead}, In1),
{FileName, Comment, BExtra} =
- get_name_extra_comment(B2, FileNameLen, ExtraLen, CommentLen),
+ get_name_extra_comment(B2, FileNameLen, ExtraLen, CommentLen, GPFlag),
Acc1 = RawIterator(CD, FileName, Comment, BExtra, Acc0),
get_cd_loop(N-1, In2, RawIterator, Input, Acc1).
-get_name_extra_comment(B, FileNameLen, ExtraLen, CommentLen) ->
- case B of
- <<BFileName:FileNameLen/binary,
- BExtra:ExtraLen/binary,
- BComment:CommentLen/binary>> ->
- {binary_to_list(BFileName), binary_to_list(BComment), BExtra};
- _ ->
- throw(bad_central_directory)
+get_name_extra_comment(B, FileNameLen, ExtraLen, CommentLen, GPFlag) ->
+ try
+ <<BFileName:FileNameLen/binary,
+ BExtra:ExtraLen/binary,
+ BComment:CommentLen/binary>> = B,
+ {binary_to_chars(BFileName, GPFlag),
+ %% Appendix D says: "If general purpose bit 11 is unset, the
+ %% file name and comment should conform to the original ZIP
+ %% character encoding." However, it seems that at least Linux
+ %% zip(1) encodes the comment without setting bit 11 if the
+ %% filename is 7-bit ASCII. If bit 11 is set,
+ %% binary_to_chars/1 could (should?) be called (it can fail),
+ %% but the choice is to employ heuristics in this case too
+ %% (it does not fail).
+ heuristic_to_string(BComment),
+ BExtra}
+ catch
+ _:_ ->
+ throw(bad_central_directory)
end.
%% get end record, containing the offset to the central directory
@@ -1428,7 +1460,8 @@ get_z_file(In0, Z, Input, Output, OpO, FB,
LH#local_file_header.crc32}
end,
{BFileN, In3} = Input({read, FileNameLen + ExtraLen}, In1),
- {FileName, _} = get_file_name_extra(FileNameLen, ExtraLen, BFileN),
+ {FileName, _} =
+ get_file_name_extra(FileNameLen, ExtraLen, BFileN, GPFlag),
ReadAndWrite =
case check_valid_location(CWD, FileName) of
{true,FileName1} ->
@@ -1488,12 +1521,13 @@ check_dir_level([".." | Parts], Level) ->
check_dir_level([_Dir | Parts], Level) ->
check_dir_level(Parts, Level+1).
-get_file_name_extra(FileNameLen, ExtraLen, B) ->
- case B of
- <<BFileName:FileNameLen/binary, BExtra:ExtraLen/binary>> ->
- {binary_to_list(BFileName), BExtra};
- _ ->
- throw(bad_file_header)
+get_file_name_extra(FileNameLen, ExtraLen, B, GPFlag) ->
+ try
+ <<BFileName:FileNameLen/binary, BExtra:ExtraLen/binary>> = B,
+ {binary_to_chars(BFileName, GPFlag), BExtra}
+ catch
+ _:_ ->
+ throw(bad_file_header)
end.
%% get compressed or stored data
@@ -1597,6 +1631,38 @@ skip_bin(B, Pos) when is_binary(B) ->
_ -> <<>>
end.
+binary_to_chars(B, GPFlag) ->
+ ?SHOW_GP_BIT_11(B, GPFlag band ?GP_BIT_11),
+ case GPFlag band ?GP_BIT_11 of
+ 0 ->
+ binary_to_list(B);
+ ?GP_BIT_11 ->
+ case unicode:characters_to_list(B) of
+ List when is_list(List) ->
+ List
+ end
+ end.
+
+heuristic_to_string(B) when is_binary(B) ->
+ case unicode:characters_to_binary(B) of
+ B ->
+ unicode:characters_to_list(B);
+ _ ->
+ binary_to_list(B)
+ end.
+
+encode_string(String) ->
+ case lists:any(fun(C) -> C > 127 end, String) of
+ true ->
+ case unicode:characters_to_binary(String) of
+ B when is_binary(B) ->
+ {binary_to_list(B), ?GP_BIT_11};
+ _ ->
+ throw({bad_unicode, String})
+ end;
+ false ->
+ {String, 0}
+ end.
%% ZIP header manipulations
eocd_and_comment_from_bin(<<DiskNum:16/little,