aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r--lib/stdlib/src/Makefile1
-rw-r--r--lib/stdlib/src/array.erl102
-rw-r--r--lib/stdlib/src/beam_lib.erl2
-rw-r--r--lib/stdlib/src/binary.erl8
-rw-r--r--lib/stdlib/src/c.erl30
-rw-r--r--lib/stdlib/src/dets.erl128
-rw-r--r--lib/stdlib/src/dets_server.erl24
-rw-r--r--lib/stdlib/src/dets_utils.erl24
-rw-r--r--lib/stdlib/src/dets_v8.erl8
-rw-r--r--lib/stdlib/src/dets_v9.erl14
-rw-r--r--lib/stdlib/src/dict.erl131
-rw-r--r--lib/stdlib/src/digraph.erl98
-rw-r--r--lib/stdlib/src/digraph_utils.erl46
-rw-r--r--lib/stdlib/src/edlin.erl5
-rw-r--r--lib/stdlib/src/edlin_expand.erl8
-rw-r--r--lib/stdlib/src/epp.erl201
-rw-r--r--lib/stdlib/src/erl_compile.erl243
-rw-r--r--lib/stdlib/src/erl_eval.erl244
-rw-r--r--lib/stdlib/src/erl_expand_records.erl60
-rw-r--r--lib/stdlib/src/erl_internal.erl7
-rw-r--r--lib/stdlib/src/erl_lint.erl422
-rw-r--r--lib/stdlib/src/erl_parse.yrl154
-rw-r--r--lib/stdlib/src/erl_pp.erl60
-rw-r--r--lib/stdlib/src/erl_scan.erl12
-rw-r--r--lib/stdlib/src/erl_tar.erl167
-rw-r--r--lib/stdlib/src/error_logger_tty_h.erl11
-rw-r--r--lib/stdlib/src/escript.erl23
-rw-r--r--lib/stdlib/src/ets.erl74
-rw-r--r--lib/stdlib/src/eval_bits.erl19
-rw-r--r--lib/stdlib/src/file_sorter.erl32
-rw-r--r--lib/stdlib/src/filelib.erl16
-rw-r--r--lib/stdlib/src/filename.erl6
-rw-r--r--lib/stdlib/src/gb_sets.erl168
-rw-r--r--lib/stdlib/src/gb_trees.erl140
-rw-r--r--lib/stdlib/src/gen.erl6
-rw-r--r--lib/stdlib/src/gen_event.erl85
-rw-r--r--lib/stdlib/src/gen_fsm.erl71
-rw-r--r--lib/stdlib/src/gen_server.erl214
-rw-r--r--lib/stdlib/src/io.erl53
-rw-r--r--lib/stdlib/src/io_lib.erl17
-rw-r--r--lib/stdlib/src/io_lib_format.erl2
-rw-r--r--lib/stdlib/src/io_lib_pretty.erl53
-rw-r--r--lib/stdlib/src/lists.erl15
-rw-r--r--lib/stdlib/src/log_mf_h.erl13
-rw-r--r--lib/stdlib/src/maps.erl214
-rw-r--r--lib/stdlib/src/ms_transform.erl13
-rw-r--r--lib/stdlib/src/orddict.erl16
-rw-r--r--lib/stdlib/src/otp_internal.erl83
-rw-r--r--lib/stdlib/src/pg.erl3
-rw-r--r--lib/stdlib/src/pool.erl4
-rw-r--r--lib/stdlib/src/proc_lib.erl6
-rw-r--r--lib/stdlib/src/qlc.erl2
-rw-r--r--lib/stdlib/src/qlc_pt.erl27
-rw-r--r--lib/stdlib/src/queue.erl75
-rw-r--r--lib/stdlib/src/re.erl177
-rw-r--r--lib/stdlib/src/sets.erl116
-rw-r--r--lib/stdlib/src/shell.erl23
-rw-r--r--lib/stdlib/src/slave.erl49
-rw-r--r--lib/stdlib/src/sofs.erl10
-rw-r--r--lib/stdlib/src/stdlib.app.src6
-rw-r--r--lib/stdlib/src/stdlib.appup.src18
-rw-r--r--lib/stdlib/src/string.erl1
-rw-r--r--lib/stdlib/src/supervisor.erl68
-rw-r--r--lib/stdlib/src/supervisor_bridge.erl11
-rw-r--r--lib/stdlib/src/sys.erl79
-rw-r--r--lib/stdlib/src/timer.erl2
-rw-r--r--lib/stdlib/src/zip.erl37
67 files changed, 2895 insertions, 1362 deletions
diff --git a/lib/stdlib/src/Makefile b/lib/stdlib/src/Makefile
index f3387d669b..9ab2cd4134 100644
--- a/lib/stdlib/src/Makefile
+++ b/lib/stdlib/src/Makefile
@@ -91,6 +91,7 @@ MODULES= \
lib \
lists \
log_mf_h \
+ maps \
math \
ms_transform \
otp_internal \
diff --git a/lib/stdlib/src/array.erl b/lib/stdlib/src/array.erl
index 2f69e2b0a4..10d2ccea45 100644
--- a/lib/stdlib/src/array.erl
+++ b/lib/stdlib/src/array.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2007-2011. All Rights Reserved.
+%% Copyright Ericsson AB 2007-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -86,6 +86,8 @@
foldr/3, sparse_foldl/3, sparse_foldr/3, fix/1, relax/1, is_fix/1,
resize/1, resize/2]).
+-export_type([array/0, array/1]).
+
%%-define(TEST,1).
-ifdef(TEST).
-include_lib("eunit/include/eunit.hrl").
@@ -144,18 +146,28 @@
%%--------------------------------------------------------------------------
+-type element_tuple(T) ::
+ {T, T, T, T, T, T, T, T, T, T}
+ | {element_tuple(T), element_tuple(T), element_tuple(T),
+ element_tuple(T), element_tuple(T), element_tuple(T),
+ element_tuple(T), element_tuple(T), element_tuple(T),
+ element_tuple(T), non_neg_integer()}.
+
+-type elements(T) :: non_neg_integer()
+ | element_tuple(T)
+ | nil(). % kill reference, for GC
+
-record(array, {size :: non_neg_integer(), %% number of defined entries
max :: non_neg_integer(), %% maximum number of entries
%% in current tree
default, %% the default value (usually 'undefined')
- elements %% the tuple tree
+ elements :: elements(_) %% the tuple tree
}).
-%% A declaration equivalent to the following one is hard-coded in erl_types.
-%% That declaration contains hard-coded information about the #array{}
-%% structure and the types of its fields. So, please make sure that any
-%% changes to its structure are also propagated to erl_types.erl.
-%%
-%% -opaque array() :: #array{}.
+
+-opaque array() :: array(term()).
+
+-opaque array(Type) ::
+ #array{default :: Type, elements :: elements(Type)}.
%%
%% Types
@@ -164,13 +176,13 @@
-type array_indx() :: non_neg_integer().
-type array_opt() :: {'fixed', boolean()} | 'fixed'
- | {'default', Value :: term()}
+ | {'default', Type :: term()}
| {'size', N :: non_neg_integer()}
| (N :: non_neg_integer()).
-type array_opts() :: array_opt() | [array_opt()].
--type indx_pair() :: {Index :: array_indx(), Value :: term()}.
--type indx_pairs() :: [indx_pair()].
+-type indx_pair(Type) :: {Index :: array_indx(), Type}.
+-type indx_pairs(Type) :: [indx_pair(Type)].
%%--------------------------------------------------------------------------
@@ -321,7 +333,7 @@ size(_) -> erlang:error(badarg).
%%
%% @see new/2
--spec default(Array :: array()) -> term().
+-spec default(Array :: array(Type)) -> Value :: Type.
default(#array{default = D}) -> D;
default(_) -> erlang:error(badarg).
@@ -404,7 +416,7 @@ new_test_() ->
%% automatically upon insertion; see also {@link set/3}.
%% @see relax/1
--spec fix(Array :: array()) -> array().
+-spec fix(Array :: array(Type)) -> array(Type).
fix(#array{}=A) ->
A#array{max = 0}.
@@ -452,7 +464,7 @@ fix_test_() ->
%% fix/1}.)
%% @see fix/1
--spec relax(Array :: array()) -> array().
+-spec relax(Array :: array(Type)) -> array(Type).
relax(#array{size = N}=A) ->
A#array{max = find_max(N-1, ?LEAFSIZE)}.
@@ -477,7 +489,8 @@ relax_test_() ->
%% integer, the call fails with reason `badarg'. If the given array has
%% fixed size, the resulting array will also have fixed size.
--spec resize(Size :: non_neg_integer(), Array :: array()) -> array().
+-spec resize(Size :: non_neg_integer(), Array :: array(Type)) ->
+ array(Type).
resize(Size, #array{size = N, max = M, elements = E}=A)
when is_integer(Size), Size >= 0 ->
@@ -508,7 +521,7 @@ resize(_Size, _) ->
%% @see resize/2
%% @see sparse_size/1
--spec resize(Array :: array()) -> array().
+-spec resize(Array :: array(Type)) -> array(Type).
resize(Array) ->
resize(sparse_size(Array), Array).
@@ -558,7 +571,7 @@ resize_test_() ->
%% @see get/2
%% @see reset/2
--spec set(I :: array_indx(), Value :: term(), Array :: array()) -> array().
+-spec set(I :: array_indx(), Value :: Type, Array :: array(Type)) -> array(Type).
set(I, Value, #array{size = N, max = M, default = D, elements = E}=A)
when is_integer(I), I >= 0 ->
@@ -621,7 +634,7 @@ expand(I, _S, X, D) ->
%% @see set/3
--spec get(I :: array_indx(), Array :: array()) -> term().
+-spec get(I :: array_indx(), Array :: array(Type)) -> Value :: Type.
get(I, #array{size = N, max = M, elements = E, default = D})
when is_integer(I), I >= 0 ->
@@ -661,7 +674,7 @@ get_1(I, E, _D) ->
%% TODO: a reset_range function
--spec reset(I :: array_indx(), Array :: array()) -> array().
+-spec reset(I :: array_indx(), Array :: array(Type)) -> array(Type).
reset(I, #array{size = N, max = M, default = D, elements = E}=A)
when is_integer(I), I >= 0 ->
@@ -747,7 +760,7 @@ set_get_test_() ->
%% @see from_list/2
%% @see sparse_to_list/1
--spec to_list(Array :: array()) -> list().
+-spec to_list(Array :: array(Type)) -> list(Value :: Type).
to_list(#array{size = 0}) ->
[];
@@ -820,7 +833,7 @@ to_list_test_() ->
%%
%% @see to_list/1
--spec sparse_to_list(Array :: array()) -> list().
+-spec sparse_to_list(Array :: array(Type)) -> list(Value :: Type).
sparse_to_list(#array{size = 0}) ->
[];
@@ -887,7 +900,7 @@ sparse_to_list_test_() ->
%% @equiv from_list(List, undefined)
--spec from_list(List :: list()) -> array().
+-spec from_list(List :: list(Value :: Type)) -> array(Type).
from_list(List) ->
from_list(List, undefined).
@@ -899,7 +912,7 @@ from_list(List) ->
%% @see new/2
%% @see to_list/1
--spec from_list(List :: list(), Default :: term()) -> array().
+-spec from_list(List :: list(Value :: Type), Default :: term()) -> array(Type).
from_list([], Default) ->
new({default,Default});
@@ -998,7 +1011,7 @@ from_list_test_() ->
%% @see from_orddict/2
%% @see sparse_to_orddict/1
--spec to_orddict(Array :: array()) -> indx_pairs().
+-spec to_orddict(Array :: array(Type)) -> indx_pairs(Value :: Type).
to_orddict(#array{size = 0}) ->
[];
@@ -1035,16 +1048,16 @@ to_orddict_3(N, R, D, L, E, S) ->
to_orddict_2(element(N, E), R, D, L),
E, S).
--spec push_pairs(non_neg_integer(), array_indx(), term(), indx_pairs()) ->
- indx_pairs().
+-spec push_pairs(non_neg_integer(), array_indx(), term(), indx_pairs(Type)) ->
+ indx_pairs(Type).
push_pairs(0, _I, _E, L) ->
L;
push_pairs(N, I, E, L) ->
push_pairs(N-1, I-1, E, [{I, E} | L]).
--spec push_tuple_pairs(non_neg_integer(), array_indx(), term(), indx_pairs()) ->
- indx_pairs().
+-spec push_tuple_pairs(non_neg_integer(), array_indx(), term(), indx_pairs(Type)) ->
+ indx_pairs(Type).
push_tuple_pairs(0, _I, _T, L) ->
L;
@@ -1090,7 +1103,7 @@ to_orddict_test_() ->
%%
%% @see to_orddict/1
--spec sparse_to_orddict(Array :: array()) -> indx_pairs().
+-spec sparse_to_orddict(Array :: array(Type)) -> indx_pairs(Value :: Type).
sparse_to_orddict(#array{size = 0}) ->
[];
@@ -1128,7 +1141,7 @@ sparse_to_orddict_3(N, R, D, L, E, S) ->
E, S).
-spec sparse_push_tuple_pairs(non_neg_integer(), array_indx(),
- _, _, indx_pairs()) -> indx_pairs().
+ _, _, indx_pairs(Type)) -> indx_pairs(Type).
sparse_push_tuple_pairs(0, _I, _D, _T, L) ->
L;
@@ -1170,7 +1183,7 @@ sparse_to_orddict_test_() ->
%% @equiv from_orddict(Orddict, undefined)
--spec from_orddict(Orddict :: indx_pairs()) -> array().
+-spec from_orddict(Orddict :: indx_pairs(Value :: Type)) -> array(Type).
from_orddict(Orddict) ->
from_orddict(Orddict, undefined).
@@ -1184,7 +1197,8 @@ from_orddict(Orddict) ->
%% @see new/2
%% @see to_orddict/1
--spec from_orddict(Orddict :: indx_pairs(), Default :: term()) -> array().
+-spec from_orddict(Orddict :: indx_pairs(Value :: Type), Default :: Type) ->
+ array(Type).
from_orddict([], Default) ->
new({default,Default});
@@ -1379,8 +1393,8 @@ from_orddict_test_() ->
%% @see foldr/3
%% @see sparse_map/2
--spec map(Function, Array :: array()) -> array() when
- Function :: fun((Index :: array_indx(), Value :: _) -> _).
+-spec map(Function, Array :: array(Type1)) -> array(Type2) when
+ Function :: fun((Index :: array_indx(), Type1) -> Type2).
map(Function, Array=#array{size = N, elements = E, default = D})
when is_function(Function, 2) ->
@@ -1471,8 +1485,8 @@ map_test_() ->
%%
%% @see map/2
--spec sparse_map(Function, Array :: array()) -> array() when
- Function :: fun((Index :: array_indx(), Value :: _) -> _).
+-spec sparse_map(Function, Array :: array(Type1)) -> array(Type2) when
+ Function :: fun((Index :: array_indx(), Type1) -> Type2).
sparse_map(Function, Array=#array{size = N, elements = E, default = D})
when is_function(Function, 2) ->
@@ -1567,8 +1581,8 @@ sparse_map_test_() ->
%% @see map/2
%% @see sparse_foldl/3
--spec foldl(Function, InitialAcc :: A, Array :: array()) -> B when
- Function :: fun((Index :: array_indx(), Value :: _, Acc :: A) -> B).
+-spec foldl(Function, InitialAcc :: A, Array :: array(Type)) -> B when
+ Function :: fun((Index :: array_indx(), Value :: Type, Acc :: A) -> B).
foldl(Function, A, #array{size = N, elements = E, default = D})
when is_function(Function, 3) ->
@@ -1640,8 +1654,8 @@ foldl_test_() ->
%% @see foldl/3
%% @see sparse_foldr/3
--spec sparse_foldl(Function, InitialAcc :: A, Array :: array()) -> B when
- Function :: fun((Index :: array_indx(), Value :: _, Acc :: A) -> B).
+-spec sparse_foldl(Function, InitialAcc :: A, Array :: array(Type)) -> B when
+ Function :: fun((Index :: array_indx(), Value :: Type, Acc :: A) -> B).
sparse_foldl(Function, A, #array{size = N, elements = E, default = D})
when is_function(Function, 3) ->
@@ -1717,8 +1731,8 @@ sparse_foldl_test_() ->
%% @see foldl/3
%% @see map/2
--spec foldr(Function, InitialAcc :: A, Array :: array()) -> B when
- Function :: fun((Index :: array_indx(), Value :: _, Acc :: A) -> B).
+-spec foldr(Function, InitialAcc :: A, Array :: array(Type)) -> B when
+ Function :: fun((Index :: array_indx(), Value :: Type, Acc :: A) -> B).
foldr(Function, A, #array{size = N, elements = E, default = D})
when is_function(Function, 3) ->
@@ -1796,8 +1810,8 @@ foldr_test_() ->
%% @see foldr/3
%% @see sparse_foldl/3
--spec sparse_foldr(Function, InitialAcc :: A, Array :: array()) -> B when
- Function :: fun((Index :: array_indx(), Value :: _, Acc :: A) -> B).
+-spec sparse_foldr(Function, InitialAcc :: A, Array :: array(Type)) -> B when
+ Function :: fun((Index :: array_indx(), Value :: Type, Acc :: A) -> B).
sparse_foldr(Function, A, #array{size = N, elements = E, default = D})
when is_function(Function, 3) ->
diff --git a/lib/stdlib/src/beam_lib.erl b/lib/stdlib/src/beam_lib.erl
index 121f9febed..1a7b7d5a5e 100644
--- a/lib/stdlib/src/beam_lib.erl
+++ b/lib/stdlib/src/beam_lib.erl
@@ -904,7 +904,7 @@ call_crypto_server(Req) ->
end.
call_crypto_server_1(Req) ->
- gen_server:start({local,?CRYPTO_KEY_SERVER}, ?MODULE, [], []),
+ {ok, _} = gen_server:start({local,?CRYPTO_KEY_SERVER}, ?MODULE, [], []),
erlang:yield(),
call_crypto_server(Req).
diff --git a/lib/stdlib/src/binary.erl b/lib/stdlib/src/binary.erl
index 4850a59eb6..8d07a356dd 100644
--- a/lib/stdlib/src/binary.erl
+++ b/lib/stdlib/src/binary.erl
@@ -89,9 +89,9 @@ copy(_, _) ->
decode_unsigned(_) ->
erlang:nif_error(undef).
--spec decode_unsigned(Subject, Endianess) -> Unsigned when
+-spec decode_unsigned(Subject, Endianness) -> Unsigned when
Subject :: binary(),
- Endianess :: big | little,
+ Endianness :: big | little,
Unsigned :: non_neg_integer().
decode_unsigned(_, _) ->
@@ -103,9 +103,9 @@ decode_unsigned(_, _) ->
encode_unsigned(_) ->
erlang:nif_error(undef).
--spec encode_unsigned(Unsigned, Endianess) -> binary() when
+-spec encode_unsigned(Unsigned, Endianness) -> binary() when
Unsigned :: non_neg_integer(),
- Endianess :: big | little.
+ Endianness :: big | little.
encode_unsigned(_, _) ->
erlang:nif_error(undef).
diff --git a/lib/stdlib/src/c.erl b/lib/stdlib/src/c.erl
index 6e96e3d564..9860adf04d 100644
--- a/lib/stdlib/src/c.erl
+++ b/lib/stdlib/src/c.erl
@@ -330,13 +330,18 @@ choice(F) ->
end.
get_line(P, Default) ->
- case io:get_line(P) of
+ case line_string(io:get_line(P)) of
"\n" ->
Default;
L ->
L
end.
+%% If the standard input is set to binary mode
+%% convert it to a list so we can properly match.
+line_string(Binary) when is_binary(Binary) -> unicode:characters_to_list(Binary);
+line_string(Other) -> Other.
+
mfa_string(Fun) when is_function(Fun) ->
{module,M} = erlang:fun_info(Fun, module),
{name,F} = erlang:fun_info(Fun, name),
@@ -450,7 +455,7 @@ m() ->
foreach(fun ({Mod,File}) -> mformat(Mod, File) end, sort(code:all_loaded())).
mformat(A1, A2) ->
- format("~-20s ~s\n", [A1,A2]).
+ format("~-20s ~ts\n", [A1,A2]).
%% erlangrc(Home)
%% Try to run a ".erlang" file, first in the current directory
@@ -504,9 +509,12 @@ m(M) ->
{exports,E} = lists:keyfind(exports, 1, L),
Time = get_compile_time(L),
COpts = get_compile_options(L),
- format("Module ~w compiled: ",[M]), print_time(Time),
- format("Compiler options: ~p~n", [COpts]),
+ format("Module: ~w~n", [M]),
+ print_md5(L),
+ format("Compiled: "),
+ print_time(Time),
print_object_file(M),
+ format("Compiler options: ~p~n", [COpts]),
format("Exports: ~n",[]), print_exports(keysort(1, E)).
print_object_file(Mod) ->
@@ -517,6 +525,12 @@ print_object_file(Mod) ->
ignore
end.
+print_md5(L) ->
+ case lists:keyfind(md5, 1, L) of
+ {md5,<<MD5:128>>} -> io:format("MD5: ~.16b~n",[MD5]);
+ _ -> ok
+ end.
+
get_compile_time(L) ->
case get_compile_info(L, time) of
{ok,Val} -> Val;
@@ -564,8 +578,8 @@ split_print_exports([{F1, A1}|T1], [{F2, A2} | T2]) ->
split_print_exports([], []) -> ok.
print_time({Year,Month,Day,Hour,Min,_Secs}) ->
- format("Date: ~s ~w ~w, ", [month(Month),Day,Year]),
- format("Time: ~.2.0w.~.2.0w~n", [Hour,Min]);
+ format("~s ~w ~w, ", [month(Month),Day,Year]),
+ format("~.2.0w:~.2.0w~n", [Hour,Min]);
print_time(notime) ->
format("No compile time info available~n",[]).
@@ -694,7 +708,7 @@ pwd() ->
Dir :: file:name().
cd(Dir) ->
- file:set_cwd(Dir),
+ _ = file:set_cwd(Dir),
pwd().
%% ls()
@@ -716,7 +730,7 @@ ls(Dir) ->
{error, enotdir} ->
ls_print([Dir]);
{error, Error} ->
- format("~s\n", [file:format_error(Error)])
+ format("~ts\n", [file:format_error(Error)])
end.
ls_print([]) -> ok;
diff --git a/lib/stdlib/src/dets.erl b/lib/stdlib/src/dets.erl
index 68b157c13c..a4bd45ea19 100644
--- a/lib/stdlib/src/dets.erl
+++ b/lib/stdlib/src/dets.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -440,9 +440,10 @@ insert(Tab, Objs) when is_list(Objs) ->
insert(Tab, Obj) ->
badarg(treq(Tab, {insert, [Obj]}), [Tab, Obj]).
--spec insert_new(Name, Objects) -> boolean() when
+-spec insert_new(Name, Objects) -> boolean() | {'error', Reason} when
Name :: tab_name(),
- Objects :: object() | [object()].
+ Objects :: object() | [object()],
+ Reason :: term().
insert_new(Tab, Objs) when is_list(Objs) ->
badarg(treq(Tab, {insert_new, Objs}), [Tab, Objs]);
@@ -469,7 +470,7 @@ is_compatible_bchunk_format(Tab, Term) ->
is_dets_file(FileName) ->
case catch read_file_header(FileName, read, false) of
{ok, Fd, FH} ->
- file:close(Fd),
+ _ = file:close(Fd),
FH#fileheader.cookie =:= ?MAGIC;
{error, {tooshort, _}} ->
false;
@@ -1384,7 +1385,8 @@ do_apply_op(Op, From, Head, N) ->
end,
if
From =/= self() ->
- From ! {self(), {error, {dets_bug, Name, Op, Bad}}};
+ From ! {self(), {error, {dets_bug, Name, Op, Bad}}},
+ ok;
true -> % auto_save | may_grow | {delayed_write, _}
ok
end,
@@ -1634,7 +1636,8 @@ start_auto_save_timer(Head) when Head#head.auto_save =:= infinity ->
ok;
start_auto_save_timer(Head) ->
Millis = Head#head.auto_save,
- erlang:send_after(Millis, self(), ?DETS_CALL(self(), auto_save)).
+ _Ref = erlang:send_after(Millis, self(), ?DETS_CALL(self(), auto_save)),
+ ok.
%% Version 9: Peek the message queue and try to evaluate several
%% lookup requests in parallel. Evalute delete_object, delete and
@@ -1683,7 +1686,7 @@ stream_end(Head, Pids0, C, N, Next) ->
%% replies to delete and insert requests even if the
%% latter requests were made before the lookup requests,
%% which can be confusing.)
- lookup_replies(Found),
+ _ = lookup_replies(Found),
stream_end1(Pids0, Next, N, C, Head1, PwriteList);
Head1 when is_record(Head1, head) ->
stream_end2(Pids0, Pids0, Next, N, C, Head1, ok);
@@ -1733,7 +1736,7 @@ lookup_replies(Q) ->
lookup_replies(P, O, []) ->
lookup_reply(P, O);
lookup_replies(P, O, [{P2,O2} | L]) ->
- lookup_reply(P, O),
+ _ = lookup_reply(P, O),
lookup_replies(P2, lists:append(O2), L).
%% If a list of Pid then op was {member, Key}. Inlined.
@@ -1783,6 +1786,7 @@ read_file_header(FileName, Access, RamFile) ->
Version =:= 9 ->
dets_v9:read_file_header(Fd, FileName);
true ->
+ _ = file:close(Fd),
throw({error, {not_a_dets_file, FileName}})
end.
@@ -1790,12 +1794,15 @@ fclose(Head) ->
{Head1, Res} = perform_save(Head, false),
case Head1#head.ram_file of
true ->
- ignore;
+ Res;
false ->
dets_utils:stop_disk_map(),
- file:close(Head1#head.fptr)
- end,
- Res.
+ Res2 = file:close(Head1#head.fptr),
+ if
+ Res2 =:= ok -> Res;
+ true -> Res2
+ end
+ end.
%% -> {NewHead, Res}
perform_save(Head, DoSync) when Head#head.update_mode =:= dirty;
@@ -2002,7 +2009,7 @@ remove_fix(Head, Pid, How) ->
end.
do_stop(Head) ->
- unlink_fixing_procs(Head),
+ _NewHead = unlink_fixing_procs(Head),
fclose(Head).
unlink_fixing_procs(Head) ->
@@ -2010,7 +2017,7 @@ unlink_fixing_procs(Head) ->
false ->
Head;
{_, Counters} ->
- lists:map(fun({Pid, _Counter}) -> unlink(Pid) end, Counters),
+ lists:foreach(fun({Pid, _Counter}) -> unlink(Pid) end, Counters),
Head#head{fixed = false,
freelists = dets_utils:get_freelists(Head)}
end.
@@ -2021,8 +2028,9 @@ check_growth(Head) ->
NoThings = no_things(Head),
if
NoThings > Head#head.next ->
- erlang:send_after(200, self(),
- ?DETS_CALL(self(), may_grow)); % Catch up.
+ _Ref = erlang:send_after
+ (200, self(), ?DETS_CALL(self(), may_grow)), % Catch up.
+ ok;
true ->
ok
end.
@@ -2107,6 +2115,8 @@ test_bchunk_format(Head, Term) ->
do_open_file([Fname, Verbose], Parent, Server, Ref) ->
case catch fopen2(Fname, Ref) of
+ {error, {tooshort, _}} ->
+ err({error, {not_a_dets_file, Fname}});
{error, _Reason} = Error ->
err(Error);
{ok, Head} ->
@@ -2120,11 +2130,10 @@ do_open_file([Fname, Verbose], Parent, Server, Ref) ->
[Bad]),
{error, {dets_bug, Fname, Bad}}
end;
-do_open_file([Tab, OpenArgs, Verb], Parent, Server, Ref) ->
+do_open_file([Tab, OpenArgs, Verb], Parent, Server, _Ref) ->
case catch fopen3(Tab, OpenArgs) of
{error, {tooshort, _}} ->
- file:delete(OpenArgs#open_args.file),
- do_open_file([Tab, OpenArgs, Verb], Parent, Server, Ref);
+ err({error, {not_a_dets_file, OpenArgs#open_args.file}});
{error, _Reason} = Error ->
err(Error);
{ok, Head} ->
@@ -2480,7 +2489,6 @@ fopen2(Fname, Tab) ->
{ok, _} ->
Acc = read_write,
Ram = false,
- %% Fd is not always closed upon error, but exit is soon called.
{ok, Fd, FH} = read_file_header(Fname, Acc, Ram),
Mod = FH#fileheader.mod,
Do = case Mod:check_file_header(FH, Fd) of
@@ -2536,7 +2544,6 @@ fopen_existing_file(Tab, OpenArgs) ->
ram_file = Ram, delayed_write = CacheSz, auto_save =
Auto, access = Acc, version = Version, debug = Debug} =
OpenArgs,
- %% Fd is not always closed upon error, but exit is soon called.
{ok, Fd, FH} = read_file_header(Fname, Acc, Ram),
V9 = (Version =:= 9) or (Version =:= default),
MinF = (MinSlots =:= default) or (MinSlots =:= FH#fileheader.min_no_slots),
@@ -2671,11 +2678,11 @@ fopen_init_file(Tab, OpenArgs) ->
case catch Mod:initiate_file(Fd, Tab, Fname, Type, Kp, MinSlots, MaxSlots,
Ram, CacheSz, Auto, true) of
{error, Reason} when Ram ->
- file:close(Fd),
+ _ = file:close(Fd),
throw({error, Reason});
{error, Reason} ->
- file:close(Fd),
- file:delete(Fname),
+ _ = file:close(Fd),
+ _ = file:delete(Fname),
throw({error, Reason});
{ok, Head} ->
start_auto_save_timer(Head),
@@ -2730,8 +2737,8 @@ compact(SourceHead) ->
{ok, H} ->
H;
Error ->
- file:close(Fd),
- file:delete(Tmp),
+ _ = file:close(Fd),
+ _ = file:delete(Tmp),
throw(Error)
end,
@@ -2748,12 +2755,12 @@ compact(SourceHead) ->
if
R =:= ok -> ok;
true ->
- file:delete(Tmp),
+ _ = file:delete(Tmp),
throw(R)
end;
Err ->
- file:close(Fd),
- file:delete(Tmp),
+ _ = file:close(Fd),
+ _ = file:delete(Tmp),
throw(Err)
end.
@@ -2777,7 +2784,7 @@ fsck(Fd, Tab, Fname, FH, MinSlotsArg, MaxSlotsArg, Version) ->
BetterSlotNumbers = {MinSlots, BetterNoSlots, MaxSlots},
case fsck_try(Fd, Tab, FH, Fname, BetterSlotNumbers, Version) of
{try_again, _} ->
- file:close(Fd),
+ _ = file:close(Fd),
{error, {cannot_repair, Fname}};
Else ->
Else
@@ -2818,31 +2825,36 @@ fsck_try(Fd, Tab, FH, Fname, SlotNumbers, Version) ->
if
R =:= ok -> ok;
true ->
- file:delete(Tmp),
+ _ = file:delete(Tmp),
R
end;
TryAgainOrError ->
- file:delete(Tmp),
+ _ = file:delete(Tmp),
TryAgainOrError
end;
Error ->
- file:close(Fd),
+ _ = file:close(Fd),
Error
end.
tempfile(Fname) ->
Tmp = lists:concat([Fname, ".TMP"]),
- tempfile(Tmp, 10).
-
-tempfile(Tmp, 0) ->
- Tmp;
-tempfile(Tmp, N) ->
case file:delete(Tmp) of
- {error, eacces} -> % 'dets_process_died' happened anyway... (W-nd-ws)
- timer:sleep(1000),
- tempfile(Tmp, N-1);
- _ ->
- Tmp
+ {error, _Reason} -> % typically enoent
+ ok;
+ ok ->
+ assure_no_file(Tmp)
+ end,
+ Tmp.
+
+assure_no_file(File) ->
+ case file:read_file_info(File) of
+ {ok, _FileInfo} ->
+ %% Wait for some other process to close the file:
+ timer:sleep(100),
+ assure_no_file(File);
+ {error, _} ->
+ ok
end.
%% -> {ok, NewHead} | {try_again, integer()} | Error
@@ -2855,13 +2867,13 @@ fsck_try_est(Head, Fd, Fname, SlotNumbers, FH) ->
Bulk = false,
case Reply of
{ok, NoDups, H1} ->
- file:close(Fd),
+ _ = file:close(Fd),
fsck_copy(SizeData, H1, Bulk, NoDups);
{try_again, _} = Return ->
close_files(Bulk, SizeData, Head),
Return;
Else ->
- file:close(Fd),
+ _ = file:close(Fd),
close_files(Bulk, SizeData, Head),
Else
end.
@@ -2896,14 +2908,20 @@ fsck_copy1([SzData | L], Head, Bulk, NoDups) ->
{LogSz, Pos, {FileName, Fd}, NoObjects} = SzData,
Size = if NoObjects =:= 0 -> 0; true -> ?POW(LogSz-1) end,
ExpectedSize = Size * NoObjects,
- close_tmp(Fd),
- case file:position(Out, Pos) of
- {ok, Pos} -> ok;
- PError -> dets_utils:file_error(FileName, PError)
+ case close_tmp(Fd) of
+ ok -> ok;
+ Err ->
+ close_files(Bulk, L, Head),
+ dets_utils:file_error(FileName, Err)
end,
- {ok, Pos} = file:position(Out, Pos),
+ case file:position(Out, Pos) of
+ {ok, Pos} -> ok;
+ Err2 ->
+ close_files(Bulk, L, Head),
+ dets_utils:file_error(Head#head.filename, Err2)
+ end,
CR = file:copy({FileName, [raw,binary]}, Out),
- file:delete(FileName),
+ _ = file:delete(FileName),
case CR of
{ok, Copied} when Copied =:= ExpectedSize;
NoObjects =:= 0 -> % the segments
@@ -2937,11 +2955,11 @@ free_n_objects(Head, Addr, Size, N) ->
free_n_objects(NewHead, NewAddr, Size, N-1).
close_files(false, SizeData, Head) ->
- file:close(Head#head.fptr),
+ _ = file:close(Head#head.fptr),
close_files(true, SizeData, Head);
close_files(true, SizeData, _Head) ->
Fun = fun({_Size, _Pos, {FileName, Fd}, _No}) ->
- close_tmp(Fd),
+ _ = close_tmp(Fd),
file:delete(FileName);
(_) ->
ok
@@ -3261,7 +3279,7 @@ err(Error) ->
file_info(FileName) ->
case catch read_file_header(FileName, read, false) of
{ok, Fd, FH} ->
- file:close(Fd),
+ _ = file:close(Fd),
(FH#fileheader.mod):file_info(FH);
Other ->
Other
@@ -3290,7 +3308,7 @@ view(FileName) ->
X ->
X
end
- after file:close(Fd)
+ after _ = file:close(Fd)
end;
X ->
X
diff --git a/lib/stdlib/src/dets_server.erl b/lib/stdlib/src/dets_server.erl
index 931112088e..3164d40f35 100644
--- a/lib/stdlib/src/dets_server.erl
+++ b/lib/stdlib/src/dets_server.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2001-2009. All Rights Reserved.
+%% Copyright Ericsson AB 2001-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -171,9 +171,15 @@ handle_info({pending_reply, {Ref, Result0}}, State) ->
link(Pid),
do_link(Store, FromPid),
true = ets:insert(Store, {FromPid, Tab}),
- true = ets:insert(?REGISTRY, {Tab, 1, Pid}),
- true = ets:insert(?OWNERS, {Pid, Tab}),
+ %% do_internal_open() has already done the following:
+ %% true = ets:insert(?REGISTRY, {Tab, 1, Pid}),
+ %% true = ets:insert(?OWNERS, {Pid, Tab}),
{ok, Tab};
+ {Reply, internal_open} ->
+ %% Clean up what do_internal_open() did:
+ true = ets:delete(?REGISTRY, Tab),
+ true = ets:delete(?OWNERS, Pid),
+ Reply;
{Reply, _} -> % ok or Error
Reply
end,
@@ -241,8 +247,8 @@ ensure_started() ->
init() ->
set_verbose(verbose_flag()),
process_flag(trap_exit, true),
- ets:new(?REGISTRY, [set, named_table]),
- ets:new(?OWNERS, [set, named_table]),
+ ?REGISTRY = ets:new(?REGISTRY, [set, named_table]),
+ ?OWNERS = ets:new(?OWNERS, [set, named_table]),
ets:new(?STORE, [duplicate_bag]).
verbose_flag() ->
@@ -309,6 +315,12 @@ do_internal_open(State, From, Args) ->
[T, _, _] -> T;
[_, _] -> Ref
end,
+ %% Pretend the table is open. If someone else tries to
+ %% open the file it will always become a pending
+ %% 'add_user' request. If someone tries to use the table
+ %% there will be a delay, but that is OK.
+ true = ets:insert(?REGISTRY, {Tab, 1, Pid}),
+ true = ets:insert(?OWNERS, {Pid, Tab}),
pending_call(Tab, Pid, Ref, From, Args, internal_open, State);
Error ->
{Error, State}
@@ -338,7 +350,7 @@ handle_close(State, Req, {FromPid,_Tag}=From, Tab) ->
[{Tab, _Counter, Pid}] ->
do_unlink(Store, FromPid),
true = ets:match_delete(Store, {FromPid, Tab}),
- [true = ets:insert(Store, K) || K <- Keep],
+ true = ets:insert(Store, Keep),
ets:update_counter(?REGISTRY, Tab, -1),
pending_call(Tab, Pid, make_ref(), From, [],
remove_user, State)
diff --git a/lib/stdlib/src/dets_utils.erl b/lib/stdlib/src/dets_utils.erl
index 7bbb34dd15..6c176ad513 100644
--- a/lib/stdlib/src/dets_utils.erl
+++ b/lib/stdlib/src/dets_utils.erl
@@ -230,8 +230,12 @@ write_file(Head, Bin) ->
{ok, Fd} ->
R1 = file:write(Fd, Bin),
R2 = file:sync(Fd),
- file:close(Fd),
- if R1 =:= ok -> R2; true -> R1 end;
+ R3 = file:close(Fd),
+ case {R1, R2, R3} of
+ {ok, ok, R3} -> R3;
+ {ok, R2, _} -> R2;
+ {R1, _, _} -> R1
+ end;
Else ->
Else
end,
@@ -277,12 +281,7 @@ open(FileSpec, Args) ->
end.
truncate(Fd, FileName, Pos) ->
- if
- Pos =:= cur ->
- ok;
- true ->
- position(Fd, FileName, Pos)
- end,
+ _ = [position(Fd, FileName, Pos) || Pos =/= cur],
case file:truncate(Fd) of
ok ->
ok;
@@ -327,10 +326,10 @@ pread_close(Fd, FileName, Pos, Size) ->
{error, Error} ->
file_error_close(Fd, FileName, {error, Error});
{ok, Bin} when byte_size(Bin) < Size ->
- file:close(Fd),
+ _ = file:close(Fd),
throw({error, {tooshort, FileName}});
eof ->
- file:close(Fd),
+ _ = file:close(Fd),
throw({error, {tooshort, FileName}});
OK -> OK
end.
@@ -339,7 +338,7 @@ file_error(FileName, {error, Reason}) ->
throw({error, {file_error, FileName, Reason}}).
file_error_close(Fd, FileName, {error, Reason}) ->
- file:close(Fd),
+ _ = file:close(Fd),
throw({error, {file_error, FileName, Reason}}).
debug_mode() ->
@@ -977,7 +976,8 @@ dm([{P,<<Sz:32,X:32>>} | Bs], T) ->
true = ets:insert(T, {P,{pointer,X,Sz}}),
if
Sz =:= 0 ->
- X = 0;
+ X = 0,
+ true;
true ->
true = ets:insert(T, {{pointer,X}, P})
end,
diff --git a/lib/stdlib/src/dets_v8.erl b/lib/stdlib/src/dets_v8.erl
index 24d6e06ec8..f188502017 100644
--- a/lib/stdlib/src/dets_v8.erl
+++ b/lib/stdlib/src/dets_v8.erl
@@ -199,10 +199,10 @@
%% -> ok | throw({NewHead,Error})
mark_dirty(Head) ->
Dirty = [{?CLOSED_PROPERLY_POS, <<?NOT_PROPERLY_CLOSED:32>>}],
- dets_utils:pwrite(Head, Dirty),
- dets_utils:sync(Head),
- dets_utils:position(Head, Head#head.freelists_p),
- dets_utils:truncate(Head, cur).
+ {_NewHead, ok} = dets_utils:pwrite(Head, Dirty),
+ ok = dets_utils:sync(Head),
+ {ok, _Pos} = dets_utils:position(Head, Head#head.freelists_p),
+ ok = dets_utils:truncate(Head, cur).
%% -> {ok, head()} | throw(Error)
initiate_file(Fd, Tab, Fname, Type, Kp, MinSlots, MaxSlots,
diff --git a/lib/stdlib/src/dets_v9.erl b/lib/stdlib/src/dets_v9.erl
index 308f81c23b..2af93ec800 100644
--- a/lib/stdlib/src/dets_v9.erl
+++ b/lib/stdlib/src/dets_v9.erl
@@ -284,9 +284,9 @@
%% -> ok | throw({NewHead,Error})
mark_dirty(Head) ->
Dirty = [{?CLOSED_PROPERLY_POS, <<?NOT_PROPERLY_CLOSED:32>>}],
- dets_utils:pwrite(Head, Dirty),
- dets_utils:sync(Head),
- dets_utils:position(Head, Head#head.freelists_p),
+ {_H, ok} = dets_utils:pwrite(Head, Dirty),
+ ok = dets_utils:sync(Head),
+ {ok, _Pos} = dets_utils:position(Head, Head#head.freelists_p),
dets_utils:truncate(Head, cur).
%% -> {ok, head()} | throw(Error) | throw(badarg)
@@ -1385,13 +1385,13 @@ segment_file(SizeT, Head, FileData, SegEnd) ->
case Data of
{InFile,In0} ->
{OutFile, Out} = temp_file(Head, SizeT, I),
- file:close(In0),
+ _ = file:close(In0),
{ok, In} = dets_utils:open(InFile, [raw,binary,read]),
{ok, 0} = dets_utils:position(In, InFile, bof),
seg_file(SegAddr, SegAddr, In, InFile, Out, OutFile, SizeT,
SegEnd),
- file:close(In),
- file:delete(InFile),
+ _ = file:close(In),
+ _ = file:delete(InFile),
{OutFile,Out};
Objects ->
{LastAddr, B} = seg_file(Objects, SegAddr, SegAddr, SizeT, []),
@@ -1702,7 +1702,7 @@ free_list_to_file(Ftab, H, Pos, Sz, Ws, WsSz) ->
free_list_to_file(Ftab, H, Pos+1, Sz, NWs, NWsSz).
free_lists_from_file(H, Pos) ->
- dets_utils:position(H#head.fptr, H#head.filename, Pos),
+ {ok, Pos} = dets_utils:position(H#head.fptr, H#head.filename, Pos),
FL = dets_utils:empty_free_lists(),
case catch bin_to_tree([], H, start, FL, -1, []) of
{'EXIT', _} ->
diff --git a/lib/stdlib/src/dict.erl b/lib/stdlib/src/dict.erl
index 4b42f64609..cf8fb3114a 100644
--- a/lib/stdlib/src/dict.erl
+++ b/lib/stdlib/src/dict.erl
@@ -1,8 +1,7 @@
-%% -*- coding: utf-8 -*-
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2000-2012. All Rights Reserved.
+%% Copyright Ericsson AB 2000-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -37,11 +36,13 @@
-module(dict).
%% Standard interface.
--export([new/0,is_key/2,to_list/1,from_list/1,size/1]).
+-export([new/0,is_key/2,to_list/1,from_list/1,size/1,is_empty/1]).
-export([fetch/2,find/2,fetch_keys/1,erase/2]).
-export([store/3,append/3,append_list/3,update/3,update/4,update_counter/3]).
-export([fold/3,map/2,filter/2,merge/3]).
+-export_type([dict/0, dict/2]).
+
%% Low-level interface.
%%-export([get_slot/2,get_bucket/2,on_bucket/3,fold_dict/3,
%% maybe_expand/2,maybe_contract/2]).
@@ -54,6 +55,8 @@
-define(exp_size, (?seg_size * ?expand_load)).
-define(con_size, (?seg_size * ?contract_load)).
+-type segs(_Key, _Value) :: tuple().
+
%% Define a hashtable. The default values are the standard ones.
-record(dict,
{size=0 :: non_neg_integer(), % Number of elements
@@ -63,14 +66,13 @@
exp_size=?exp_size :: non_neg_integer(), % Size to expand at
con_size=?con_size :: non_neg_integer(), % Size to contract at
empty :: tuple(), % Empty segment
- segs :: tuple() % Segments
+ segs :: segs(_, _) % Segments
}).
-%% A declaration equivalent to the following one is hard-coded in erl_types.
-%% That declaration contains hard-coded information about the #dict{}
-%% structure and the types of its fields. So, please make sure that any
-%% changes to its structure are also propagated to erl_types.erl.
-%%
-%% -opaque dict() :: #dict{}.
+
+
+-opaque dict() :: dict(_, _).
+
+-opaque dict(Key, Value) :: #dict{segs :: segs(Key, Value)}.
-define(kv(K,V), [K|V]). % Key-Value pair format
%%-define(kv(K,V), {K,V}). % Key-Value pair format
@@ -82,8 +84,7 @@ new() ->
#dict{empty=Empty,segs={Empty}}.
-spec is_key(Key, Dict) -> boolean() when
- Key :: term(),
- Dict :: dict().
+ Dict :: dict(Key, Value :: term()).
is_key(Key, D) ->
Slot = get_slot(D, Key),
@@ -95,15 +96,15 @@ find_key(K, [_|Bkt]) -> find_key(K, Bkt);
find_key(_, []) -> false.
-spec to_list(Dict) -> List when
- Dict :: dict(),
- List :: [{Key :: term(), Value :: term()}].
+ Dict :: dict(Key, Value),
+ List :: [{Key, Value}].
to_list(D) ->
fold(fun (Key, Val, List) -> [{Key,Val}|List] end, [], D).
-spec from_list(List) -> Dict when
- List :: [{Key :: term(), Value :: term()}],
- Dict :: dict().
+ Dict :: dict(Key, Value),
+ List :: [{Key, Value}].
from_list(L) ->
lists:foldl(fun ({K,V}, D) -> store(K, V, D) end, new(), L).
@@ -113,10 +114,13 @@ from_list(L) ->
size(#dict{size=N}) when is_integer(N), N >= 0 -> N.
+-spec is_empty(Dict) -> boolean() when
+ Dict :: dict().
+
+is_empty(#dict{size=N}) -> N =:= 0.
+
-spec fetch(Key, Dict) -> Value when
- Key :: term(),
- Dict :: dict(),
- Value :: term().
+ Dict :: dict(Key, Value).
fetch(Key, D) ->
Slot = get_slot(D, Key),
@@ -131,9 +135,7 @@ fetch_val(K, [_|Bkt]) -> fetch_val(K, Bkt);
fetch_val(_, []) -> throw(badarg).
-spec find(Key, Dict) -> {'ok', Value} | 'error' when
- Key :: term(),
- Dict :: dict(),
- Value :: term().
+ Dict :: dict(Key, Value).
find(Key, D) ->
Slot = get_slot(D, Key),
@@ -145,16 +147,16 @@ find_val(K, [_|Bkt]) -> find_val(K, Bkt);
find_val(_, []) -> error.
-spec fetch_keys(Dict) -> Keys when
- Dict :: dict(),
- Keys :: [term()].
+ Dict :: dict(Key, Value :: term()),
+ Keys :: [Key].
fetch_keys(D) ->
fold(fun (Key, _Val, Keys) -> [Key|Keys] end, [], D).
-spec erase(Key, Dict1) -> Dict2 when
- Key :: term(),
- Dict1 :: dict(),
- Dict2 :: dict().
+ Dict1 :: dict(Key, Value),
+ Dict2 :: dict(Key, Value).
+
%% Erase all elements with key Key.
erase(Key, D0) ->
@@ -170,10 +172,8 @@ erase_key(Key, [E|Bkt0]) ->
erase_key(_, []) -> {[],0}.
-spec store(Key, Value, Dict1) -> Dict2 when
- Key :: term(),
- Value :: term(),
- Dict1 :: dict(),
- Dict2 :: dict().
+ Dict1 :: dict(Key, Value),
+ Dict2 :: dict(Key, Value).
store(Key, Val, D0) ->
Slot = get_slot(D0, Key),
@@ -190,10 +190,8 @@ store_bkt_val(Key, New, [Other|Bkt0]) ->
store_bkt_val(Key, New, []) -> {[?kv(Key,New)],1}.
-spec append(Key, Value, Dict1) -> Dict2 when
- Key :: term(),
- Value :: term(),
- Dict1 :: dict(),
- Dict2 :: dict().
+ Dict1 :: dict(Key, Value),
+ Dict2 :: dict(Key, Value).
append(Key, Val, D0) ->
Slot = get_slot(D0, Key),
@@ -210,10 +208,9 @@ append_bkt(Key, Val, [Other|Bkt0]) ->
append_bkt(Key, Val, []) -> {[?kv(Key,[Val])],1}.
-spec append_list(Key, ValList, Dict1) -> Dict2 when
- Key :: term(),
- ValList :: [Value :: term()],
- Dict1 :: dict(),
- Dict2 :: dict().
+ Dict1 :: dict(Key, Value),
+ Dict2 :: dict(Key, Value),
+ ValList :: [Value].
append_list(Key, L, D0) ->
Slot = get_slot(D0, Key),
@@ -284,10 +281,9 @@ app_list_bkt(Key, L, []) -> {[?kv(Key,L)],1}.
%% {[Other|Bkt1],Dc}.
-spec update(Key, Fun, Dict1) -> Dict2 when
- Key :: term(),
- Fun :: fun((Value1 :: term()) -> Value2 :: term()),
- Dict1 :: dict(),
- Dict2 :: dict().
+ Dict1 :: dict(Key, Value),
+ Dict2 :: dict(Key, Value),
+ Fun :: fun((Value1 :: Value) -> Value2 :: Value).
update(Key, F, D0) ->
Slot = get_slot(D0, Key),
@@ -307,11 +303,10 @@ update_bkt(_Key, _F, []) ->
throw(badarg).
-spec update(Key, Fun, Initial, Dict1) -> Dict2 when
- Key :: term(),
- Initial :: term(),
- Fun :: fun((Value1 :: term()) -> Value2 :: term()),
- Dict1 :: dict(),
- Dict2 :: dict().
+ Dict1 :: dict(Key, Value),
+ Dict2 :: dict(Key, Value),
+ Fun :: fun((Value1 :: Value) -> Value2 :: Value),
+ Initial :: Value.
update(Key, F, Init, D0) ->
Slot = get_slot(D0, Key),
@@ -327,10 +322,9 @@ update_bkt(Key, F, I, [Other|Bkt0]) ->
update_bkt(Key, F, I, []) when is_function(F, 1) -> {[?kv(Key,I)],1}.
-spec update_counter(Key, Increment, Dict1) -> Dict2 when
- Key :: term(),
- Increment :: number(),
- Dict1 :: dict(),
- Dict2 :: dict().
+ Dict1 :: dict(Key, Value),
+ Dict2 :: dict(Key, Value),
+ Increment :: number().
update_counter(Key, Incr, D0) when is_number(Incr) ->
Slot = get_slot(D0, Key),
@@ -347,36 +341,35 @@ counter_bkt(Key, I, []) -> {[?kv(Key,I)],1}.
-spec fold(Fun, Acc0, Dict) -> Acc1 when
Fun :: fun((Key, Value, AccIn) -> AccOut),
- Key :: term(),
- Value :: term(),
- Acc0 :: term(),
- Acc1 :: term(),
- AccIn :: term(),
- AccOut :: term(),
- Dict :: dict().
+ Dict :: dict(Key, Value),
+ Acc0 :: Acc,
+ Acc1 :: Acc,
+ AccIn :: Acc,
+ AccOut :: Acc.
+
%% Fold function Fun over all "bags" in Table and return Accumulator.
fold(F, Acc, D) -> fold_dict(F, Acc, D).
-spec map(Fun, Dict1) -> Dict2 when
- Fun :: fun((Key :: term(), Value1 :: term()) -> Value2 :: term()),
- Dict1 :: dict(),
- Dict2 :: dict().
+ Fun :: fun((Key, Value1) -> Value2),
+ Dict1 :: dict(Key, Value1),
+ Dict2 :: dict(Key, Value2).
map(F, D) -> map_dict(F, D).
-spec filter(Pred, Dict1) -> Dict2 when
- Pred :: fun((Key :: term(), Value :: term()) -> boolean()),
- Dict1 :: dict(),
- Dict2 :: dict().
+ Pred :: fun((Key , Value) -> boolean()),
+ Dict1 :: dict(Key, Value),
+ Dict2 :: dict(Key, Value).
filter(F, D) -> filter_dict(F, D).
-spec merge(Fun, Dict1, Dict2) -> Dict3 when
- Fun :: fun((Key :: term(), Value1 :: term(), Value2 :: term()) -> Value :: term()),
- Dict1 :: dict(),
- Dict2 :: dict(),
- Dict3 :: dict().
+ Fun :: fun((Key, Value1, Value2) -> Value),
+ Dict1 :: dict(Key, Value1),
+ Dict2 :: dict(Key, Value2),
+ Dict3 :: dict(Key, Value).
merge(F, D1, D2) when D1#dict.size < D2#dict.size ->
fold_dict(fun (K, V1, D) ->
diff --git a/lib/stdlib/src/digraph.erl b/lib/stdlib/src/digraph.erl
index 78f74631dc..0c21271529 100644
--- a/lib/stdlib/src/digraph.erl
+++ b/lib/stdlib/src/digraph.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2011. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -36,18 +36,14 @@
-export([get_short_path/3, get_short_cycle/2]).
--export_type([digraph/0, d_type/0, vertex/0, edge/0]).
+-export_type([graph/0, d_type/0, vertex/0, edge/0]).
-record(digraph, {vtab = notable :: ets:tab(),
etab = notable :: ets:tab(),
ntab = notable :: ets:tab(),
cyclic = true :: boolean()}).
-%% A declaration equivalent to the following one is hard-coded in erl_types.
-%% That declaration contains hard-coded information about the #digraph{}
-%% record and the types of its fields. So, please make sure that any
-%% changes to its structure are also propagated to erl_types.erl.
-%%
-%% -opaque digraph() :: #digraph{}.
+
+-opaque graph() :: #digraph{}.
-type edge() :: term().
-type label() :: term().
@@ -67,11 +63,11 @@
-type d_cyclicity() :: 'acyclic' | 'cyclic'.
-type d_type() :: d_cyclicity() | d_protection().
--spec new() -> digraph().
+-spec new() -> graph().
new() -> new([]).
--spec new(Type) -> digraph() when
+-spec new(Type) -> graph() when
Type :: [d_type()].
new(Type) ->
@@ -106,7 +102,7 @@ check_type(_, _, _) -> error.
%%
%% Set graph type
%%
--spec set_type([{'cyclic', boolean()}], digraph()) -> digraph().
+-spec set_type([{'cyclic', boolean()}], graph()) -> graph().
set_type([{cyclic,V} | Ks], G) ->
set_type(Ks, G#digraph{cyclic = V});
@@ -116,7 +112,7 @@ set_type([], G) -> G.
%% Data access functions
-spec delete(G) -> 'true' when
- G :: digraph().
+ G :: graph().
delete(G) ->
ets:delete(G#digraph.vtab),
@@ -124,7 +120,7 @@ delete(G) ->
ets:delete(G#digraph.ntab).
-spec info(G) -> InfoList when
- G :: digraph(),
+ G :: graph(),
InfoList :: [{'cyclicity', Cyclicity :: d_cyclicity()} |
{'memory', NoWords :: non_neg_integer()} |
{'protection', Protection :: d_protection()}].
@@ -142,20 +138,20 @@ info(G) ->
[{cyclicity, Cyclicity}, {memory, Memory}, {protection, Protection}].
-spec add_vertex(G) -> vertex() when
- G :: digraph().
+ G :: graph().
add_vertex(G) ->
do_add_vertex({new_vertex_id(G), []}, G).
-spec add_vertex(G, V) -> vertex() when
- G :: digraph(),
+ G :: graph(),
V :: vertex().
add_vertex(G, V) ->
do_add_vertex({V, []}, G).
-spec add_vertex(G, V, Label) -> vertex() when
- G :: digraph(),
+ G :: graph(),
V :: vertex(),
Label :: label().
@@ -163,21 +159,21 @@ add_vertex(G, V, D) ->
do_add_vertex({V, D}, G).
-spec del_vertex(G, V) -> 'true' when
- G :: digraph(),
+ G :: graph(),
V :: vertex().
del_vertex(G, V) ->
do_del_vertex(V, G).
-spec del_vertices(G, Vertices) -> 'true' when
- G :: digraph(),
+ G :: graph(),
Vertices :: [vertex()].
del_vertices(G, Vs) ->
do_del_vertices(Vs, G).
-spec vertex(G, V) -> {V, Label} | 'false' when
- G :: digraph(),
+ G :: graph(),
V :: vertex(),
Label :: label().
@@ -188,37 +184,37 @@ vertex(G, V) ->
end.
-spec no_vertices(G) -> non_neg_integer() when
- G :: digraph().
+ G :: graph().
no_vertices(G) ->
ets:info(G#digraph.vtab, size).
-spec vertices(G) -> Vertices when
- G :: digraph(),
+ G :: graph(),
Vertices :: [vertex()].
vertices(G) ->
ets:select(G#digraph.vtab, [{{'$1', '_'}, [], ['$1']}]).
--spec source_vertices(digraph()) -> [vertex()].
+-spec source_vertices(graph()) -> [vertex()].
source_vertices(G) ->
collect_vertices(G, in).
--spec sink_vertices(digraph()) -> [vertex()].
+-spec sink_vertices(graph()) -> [vertex()].
sink_vertices(G) ->
collect_vertices(G, out).
-spec in_degree(G, V) -> non_neg_integer() when
- G :: digraph(),
+ G :: graph(),
V :: vertex().
in_degree(G, V) ->
length(ets:lookup(G#digraph.ntab, {in, V})).
-spec in_neighbours(G, V) -> Vertex when
- G :: digraph(),
+ G :: graph(),
V :: vertex(),
Vertex :: [vertex()].
@@ -228,7 +224,7 @@ in_neighbours(G, V) ->
collect_elems(ets:lookup(NT, {in, V}), ET, 2).
-spec in_edges(G, V) -> Edges when
- G :: digraph(),
+ G :: graph(),
V :: vertex(),
Edges :: [edge()].
@@ -236,14 +232,14 @@ in_edges(G, V) ->
ets:select(G#digraph.ntab, [{{{in, V}, '$1'}, [], ['$1']}]).
-spec out_degree(G, V) -> non_neg_integer() when
- G :: digraph(),
+ G :: graph(),
V :: vertex().
out_degree(G, V) ->
length(ets:lookup(G#digraph.ntab, {out, V})).
-spec out_neighbours(G, V) -> Vertices when
- G :: digraph(),
+ G :: graph(),
V :: vertex(),
Vertices :: [vertex()].
@@ -253,7 +249,7 @@ out_neighbours(G, V) ->
collect_elems(ets:lookup(NT, {out, V}), ET, 3).
-spec out_edges(G, V) -> Edges when
- G :: digraph(),
+ G :: graph(),
V :: vertex(),
Edges :: [edge()].
@@ -261,7 +257,7 @@ out_edges(G, V) ->
ets:select(G#digraph.ntab, [{{{out, V}, '$1'}, [], ['$1']}]).
-spec add_edge(G, V1, V2) -> edge() | {'error', add_edge_err_rsn()} when
- G :: digraph(),
+ G :: graph(),
V1 :: vertex(),
V2 :: vertex().
@@ -269,7 +265,7 @@ add_edge(G, V1, V2) ->
do_add_edge({new_edge_id(G), V1, V2, []}, G).
-spec add_edge(G, V1, V2, Label) -> edge() | {'error', add_edge_err_rsn()} when
- G :: digraph(),
+ G :: graph(),
V1 :: vertex(),
V2 :: vertex(),
Label :: label().
@@ -278,7 +274,7 @@ add_edge(G, V1, V2, D) ->
do_add_edge({new_edge_id(G), V1, V2, D}, G).
-spec add_edge(G, E, V1, V2, Label) -> edge() | {'error', add_edge_err_rsn()} when
- G :: digraph(),
+ G :: graph(),
E :: edge(),
V1 :: vertex(),
V2 :: vertex(),
@@ -288,34 +284,34 @@ add_edge(G, E, V1, V2, D) ->
do_add_edge({E, V1, V2, D}, G).
-spec del_edge(G, E) -> 'true' when
- G :: digraph(),
+ G :: graph(),
E :: edge().
del_edge(G, E) ->
do_del_edges([E], G).
-spec del_edges(G, Edges) -> 'true' when
- G :: digraph(),
+ G :: graph(),
Edges :: [edge()].
del_edges(G, Es) ->
do_del_edges(Es, G).
-spec no_edges(G) -> non_neg_integer() when
- G :: digraph().
+ G :: graph().
no_edges(G) ->
ets:info(G#digraph.etab, size).
-spec edges(G) -> Edges when
- G :: digraph(),
+ G :: graph(),
Edges :: [edge()].
edges(G) ->
ets:select(G#digraph.etab, [{{'$1', '_', '_', '_'}, [], ['$1']}]).
-spec edges(G, V) -> Edges when
- G :: digraph(),
+ G :: graph(),
V :: vertex(),
Edges :: [edge()].
@@ -324,7 +320,7 @@ edges(G, V) ->
{{{in, V}, '$1'}, [], ['$1']}]).
-spec edge(G, E) -> {E, V1, V2, Label} | 'false' when
- G :: digraph(),
+ G :: graph(),
E :: edge(),
V1 :: vertex(),
V2 :: vertex(),
@@ -339,7 +335,7 @@ edge(G, E) ->
%%
%% Generate a "unique" edge identifier (relative to this graph)
%%
--spec new_edge_id(digraph()) -> edge().
+-spec new_edge_id(graph()) -> edge().
new_edge_id(G) ->
NT = G#digraph.ntab,
@@ -351,7 +347,7 @@ new_edge_id(G) ->
%%
%% Generate a "unique" vertex identifier (relative to this graph)
%%
--spec new_vertex_id(digraph()) -> vertex().
+-spec new_vertex_id(graph()) -> vertex().
new_vertex_id(G) ->
NT = G#digraph.ntab,
@@ -371,7 +367,7 @@ collect_elems([{_,Key}|Keys], Table, Index, Acc) ->
[ets:lookup_element(Table, Key, Index)|Acc]);
collect_elems([], _, _, Acc) -> Acc.
--spec do_add_vertex({vertex(), label()}, digraph()) -> vertex().
+-spec do_add_vertex({vertex(), label()}, graph()) -> vertex().
do_add_vertex({V, _Label} = VL, G) ->
ets:insert(G#digraph.vtab, VL),
@@ -430,14 +426,14 @@ do_del_edge(E, V1, V2, G) ->
{{{out,V1}, E}, [], [true]}]),
ets:delete(G#digraph.etab, E).
--spec rm_edges([vertex(),...], digraph()) -> 'true'.
+-spec rm_edges([vertex(),...], graph()) -> 'true'.
rm_edges([V1, V2|Vs], G) ->
rm_edge(V1, V2, G),
rm_edges([V2|Vs], G);
rm_edges(_, _) -> true.
--spec rm_edge(vertex(), vertex(), digraph()) -> 'ok'.
+-spec rm_edge(vertex(), vertex(), graph()) -> 'ok'.
rm_edge(V1, V2, G) ->
Es = out_edges(G, V1),
@@ -456,7 +452,7 @@ rm_edge_0([], _, _, #digraph{}) -> ok.
%%
%% Check that endpoints exist
%%
--spec do_add_edge({edge(), vertex(), vertex(), label()}, digraph()) ->
+-spec do_add_edge({edge(), vertex(), vertex(), label()}, graph()) ->
edge() | {'error', add_edge_err_rsn()}.
do_add_edge({E, V1, V2, Label}, G) ->
@@ -484,14 +480,14 @@ other_edge_exists(#digraph{etab = ET}, E, V1, V2) ->
false
end.
--spec do_insert_edge(edge(), vertex(), vertex(), label(), digraph()) -> edge().
+-spec do_insert_edge(edge(), vertex(), vertex(), label(), graph()) -> edge().
do_insert_edge(E, V1, V2, Label, #digraph{ntab=NT, etab=ET}) ->
ets:insert(NT, [{{out, V1}, E}, {{in, V2}, E}]),
ets:insert(ET, {E, V1, V2, Label}),
E.
--spec acyclic_add_edge(edge(), vertex(), vertex(), label(), digraph()) ->
+-spec acyclic_add_edge(edge(), vertex(), vertex(), label(), graph()) ->
edge() | {'error', {'bad_edge', [vertex()]}}.
acyclic_add_edge(_E, V1, V2, _L, _G) when V1 =:= V2 ->
@@ -507,7 +503,7 @@ acyclic_add_edge(E, V1, V2, Label, G) ->
%%
-spec del_path(G, V1, V2) -> 'true' when
- G :: digraph(),
+ G :: graph(),
V1 :: vertex(),
V2 :: vertex().
@@ -529,7 +525,7 @@ del_path(G, V1, V2) ->
%%
-spec get_cycle(G, V) -> Vertices | 'false' when
- G :: digraph(),
+ G :: graph(),
V :: vertex(),
Vertices :: [vertex(),...].
@@ -550,7 +546,7 @@ get_cycle(G, V) ->
%%
-spec get_path(G, V1, V2) -> Vertices | 'false' when
- G :: digraph(),
+ G :: graph(),
V1 :: vertex(),
V2 :: vertex(),
Vertices :: [vertex(),...].
@@ -589,7 +585,7 @@ one_path([], _, [], _, _, _, _, _Counter) -> false.
%%
-spec get_short_cycle(G, V) -> Vertices | 'false' when
- G :: digraph(),
+ G :: graph(),
V :: vertex(),
Vertices :: [vertex(),...].
@@ -602,7 +598,7 @@ get_short_cycle(G, V) ->
%%
-spec get_short_path(G, V1, V2) -> Vertices | 'false' when
- G :: digraph(),
+ G :: graph(),
V1 :: vertex(),
V2 :: vertex(),
Vertices :: [vertex(),...].
diff --git a/lib/stdlib/src/digraph_utils.erl b/lib/stdlib/src/digraph_utils.erl
index 807b5c12a1..011bcd0260 100644
--- a/lib/stdlib/src/digraph_utils.erl
+++ b/lib/stdlib/src/digraph_utils.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1999-2012. All Rights Reserved.
+%% Copyright Ericsson AB 1999-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -43,28 +43,28 @@
%%
-spec components(Digraph) -> [Component] when
- Digraph :: digraph(),
+ Digraph :: digraph:graph(),
Component :: [digraph:vertex()].
components(G) ->
forest(G, fun inout/3).
-spec strong_components(Digraph) -> [StrongComponent] when
- Digraph :: digraph(),
+ Digraph :: digraph:graph(),
StrongComponent :: [digraph:vertex()].
strong_components(G) ->
forest(G, fun in/3, revpostorder(G)).
-spec cyclic_strong_components(Digraph) -> [StrongComponent] when
- Digraph :: digraph(),
+ Digraph :: digraph:graph(),
StrongComponent :: [digraph:vertex()].
cyclic_strong_components(G) ->
remove_singletons(strong_components(G), G, []).
-spec reachable(Vertices, Digraph) -> Reachable when
- Digraph :: digraph(),
+ Digraph :: digraph:graph(),
Vertices :: [digraph:vertex()],
Reachable :: [digraph:vertex()].
@@ -72,7 +72,7 @@ reachable(Vs, G) when is_list(Vs) ->
lists:append(forest(G, fun out/3, Vs, first)).
-spec reachable_neighbours(Vertices, Digraph) -> Reachable when
- Digraph :: digraph(),
+ Digraph :: digraph:graph(),
Vertices :: [digraph:vertex()],
Reachable :: [digraph:vertex()].
@@ -80,7 +80,7 @@ reachable_neighbours(Vs, G) when is_list(Vs) ->
lists:append(forest(G, fun out/3, Vs, not_first)).
-spec reaching(Vertices, Digraph) -> Reaching when
- Digraph :: digraph(),
+ Digraph :: digraph:graph(),
Vertices :: [digraph:vertex()],
Reaching :: [digraph:vertex()].
@@ -88,7 +88,7 @@ reaching(Vs, G) when is_list(Vs) ->
lists:append(forest(G, fun in/3, Vs, first)).
-spec reaching_neighbours(Vertices, Digraph) -> Reaching when
- Digraph :: digraph(),
+ Digraph :: digraph:graph(),
Vertices :: [digraph:vertex()],
Reaching :: [digraph:vertex()].
@@ -96,7 +96,7 @@ reaching_neighbours(Vs, G) when is_list(Vs) ->
lists:append(forest(G, fun in/3, Vs, not_first)).
-spec topsort(Digraph) -> Vertices | 'false' when
- Digraph :: digraph(),
+ Digraph :: digraph:graph(),
Vertices :: [digraph:vertex()].
topsort(G) ->
@@ -107,13 +107,13 @@ topsort(G) ->
end.
-spec is_acyclic(Digraph) -> boolean() when
- Digraph :: digraph().
+ Digraph :: digraph:graph().
is_acyclic(G) ->
loop_vertices(G) =:= [] andalso topsort(G) =/= false.
-spec arborescence_root(Digraph) -> 'no' | {'yes', Root} when
- Digraph :: digraph(),
+ Digraph :: digraph:graph(),
Root :: digraph:vertex().
arborescence_root(G) ->
@@ -136,29 +136,29 @@ arborescence_root(G) ->
end.
-spec is_arborescence(Digraph) -> boolean() when
- Digraph :: digraph().
+ Digraph :: digraph:graph().
is_arborescence(G) ->
arborescence_root(G) =/= no.
-spec is_tree(Digraph) -> boolean() when
- Digraph :: digraph().
+ Digraph :: digraph:graph().
is_tree(G) ->
(digraph:no_edges(G) =:= digraph:no_vertices(G) - 1)
andalso (length(components(G)) =:= 1).
-spec loop_vertices(Digraph) -> Vertices when
- Digraph :: digraph(),
+ Digraph :: digraph:graph(),
Vertices :: [digraph:vertex()].
loop_vertices(G) ->
[V || V <- digraph:vertices(G), is_reflexive_vertex(V, G)].
-spec subgraph(Digraph, Vertices) -> SubGraph when
- Digraph :: digraph(),
+ Digraph :: digraph:graph(),
Vertices :: [digraph:vertex()],
- SubGraph :: digraph().
+ SubGraph :: digraph:graph().
subgraph(G, Vs) ->
try
@@ -169,8 +169,8 @@ subgraph(G, Vs) ->
end.
-spec subgraph(Digraph, Vertices, Options) -> SubGraph when
- Digraph :: digraph(),
- SubGraph :: digraph(),
+ Digraph :: digraph:graph(),
+ SubGraph :: digraph:graph(),
Vertices :: [digraph:vertex()],
Options :: [{'type', SubgraphType} | {'keep_labels', boolean()}],
SubgraphType :: 'inherit' | [digraph:d_type()].
@@ -184,8 +184,8 @@ subgraph(G, Vs, Opts) ->
end.
-spec condensation(Digraph) -> CondensedDigraph when
- Digraph :: digraph(),
- CondensedDigraph :: digraph().
+ Digraph :: digraph:graph(),
+ CondensedDigraph :: digraph:graph().
condensation(G) ->
SCs = strong_components(G),
@@ -209,14 +209,14 @@ condensation(G) ->
SCG.
-spec preorder(Digraph) -> Vertices when
- Digraph :: digraph(),
+ Digraph :: digraph:graph(),
Vertices :: [digraph:vertex()].
preorder(G) ->
lists:reverse(revpreorder(G)).
-spec postorder(Digraph) -> Vertices when
- Digraph :: digraph(),
+ Digraph :: digraph:graph(),
Vertices :: [digraph:vertex()].
postorder(G) ->
@@ -370,5 +370,5 @@ condense('$end_of_table', _T, _SC, _G, _SCG, _I2C) ->
condense(I, T, SC, G, SCG, I2C) ->
[{_,C}] = ets:lookup(I2C, I),
digraph:add_vertex(SCG, C),
- [digraph:add_edge(SCG, SC, C) || C =/= SC],
+ _ = [digraph:add_edge(SCG, SC, C) || C =/= SC],
condense(ets:next(T, I), T, SC, G, SCG, I2C).
diff --git a/lib/stdlib/src/edlin.erl b/lib/stdlib/src/edlin.erl
index f5998c54fd..b3bc5f6d92 100644
--- a/lib/stdlib/src/edlin.erl
+++ b/lib/stdlib/src/edlin.erl
@@ -1,8 +1,7 @@
-%% -*- coding: utf-8 -*-
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2012. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2013. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -391,7 +390,7 @@ do_op(end_of_line, Bef, [C|Aft], Rs) ->
do_op(end_of_line, Bef, [], Rs) ->
{{Bef,[]},Rs};
do_op(ctlu, Bef, Aft, Rs) ->
- put(kill_buffer, Bef),
+ put(kill_buffer, reverse(Bef)),
{{[], Aft}, [{delete_chars, -length(Bef)} | Rs]};
do_op(beep, Bef, Aft, Rs) ->
{{Bef,Aft},[beep|Rs]};
diff --git a/lib/stdlib/src/edlin_expand.erl b/lib/stdlib/src/edlin_expand.erl
index 516c0aa30b..a2b4663219 100644
--- a/lib/stdlib/src/edlin_expand.erl
+++ b/lib/stdlib/src/edlin_expand.erl
@@ -73,7 +73,7 @@ to_atom(Str) ->
error
end.
-match(Prefix, Alts, Extra) ->
+match(Prefix, Alts, Extra0) ->
Len = length(Prefix),
Matches = lists:sort(
[{S, A} || {H, A} <- Alts,
@@ -89,7 +89,11 @@ match(Prefix, Alts, Extra) ->
{yes, Remain, []}
end;
{complete, Str} ->
- {yes, nthtail(Len, Str) ++ Extra, []};
+ Extra = case {Extra0,Matches} of
+ {"(",[{Str,0}]} -> "()";
+ {_,_} -> Extra0
+ end,
+ {yes, nthtail(Len, Str) ++ Extra, []};
no ->
{no, [], []}
end.
diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl
index d1d060ebc8..5f8637c118 100644
--- a/lib/stdlib/src/epp.erl
+++ b/lib/stdlib/src/epp.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -20,12 +20,12 @@
%% An Erlang code preprocessor.
--export([open/2,open/3,open/5,close/1,format_error/1]).
+-export([open/1, open/2,open/3,open/5,close/1,format_error/1]).
-export([scan_erl_form/1,parse_erl_form/1,macro_defs/1]).
--export([parse_file/1, parse_file/3]).
+-export([parse_file/1, parse_file/2, parse_file/3]).
-export([default_encoding/0, encoding_to_string/1,
read_encoding_from_binary/1, read_encoding_from_binary/2,
- set_encoding/1, read_encoding/1, read_encoding/2]).
+ set_encoding/1, set_encoding/2, read_encoding/1, read_encoding/2]).
-export([interpret_file_attribute/1]).
-export([normalize_typed_record_fields/1,restore_typed_record_fields/1]).
@@ -33,21 +33,34 @@
-export_type([source_encoding/0]).
--type macros() :: [{atom(), term()}].
+-type macros() :: [atom() | {atom(), term()}].
-type epp_handle() :: pid().
-type source_encoding() :: latin1 | utf8.
+-type ifdef() :: 'ifdef' | 'ifndef' | 'else'.
+
+-type name() :: {'atom', atom()}.
+-type argspec() :: 'none' %No arguments
+ | non_neg_integer(). %Number of arguments
+-type tokens() :: [erl_scan:token()].
+-type used() :: {name(), argspec()}.
+
+-define(DEFAULT_ENCODING, utf8).
+
%% Epp state record.
--record(epp, {file, %Current file
- location, %Current location
- delta, %Offset from Location (-file)
- name="", %Current file name
- name2="", %-"-, modified by -file
- istk=[], %Ifdef stack
- sstk=[], %State stack
- path=[], %Include-path
- macs = dict:new() :: dict(), %Macros (don't care locations)
- uses = dict:new() :: dict(), %Macro use structure
+-record(epp, {file :: file:io_device(), %Current file
+ location=1, %Current location
+ delta=0 :: non_neg_integer(), %Offset from Location (-file)
+ name="" :: file:name(), %Current file name
+ name2="" :: file:name(), %-"-, modified by -file
+ istk=[] :: [ifdef()], %Ifdef stack
+ sstk=[] :: [#epp{}], %State stack
+ path=[] :: [file:name()], %Include-path
+ macs = dict:new() %Macros (don't care locations)
+ :: dict:dict(name(), {argspec(), tokens()}),
+ uses = dict:new() %Macro use structure
+ :: dict:dict(name(), [{argspec(), [used()]}]),
+ default_encoding = ?DEFAULT_ENCODING :: source_encoding(),
pre_opened = false :: boolean()
}).
@@ -58,6 +71,7 @@
%%% distinction in the internal representation would simplify the code
%%% a little.
+%% open(Options)
%% open(FileName, IncludePath)
%% open(FileName, IncludePath, PreDefMacros)
%% open(FileName, IoDevice, StartLocation, IncludePath, PreDefMacros)
@@ -65,6 +79,7 @@
%% scan_erl_form(Epp)
%% parse_erl_form(Epp)
%% parse_file(Epp)
+%% parse_file(FileName, Options)
%% parse_file(FileName, IncludePath, PreDefMacros)
%% macro_defs(Epp)
@@ -87,14 +102,43 @@ open(Name, Path) ->
ErrorDescriptor :: term().
open(Name, Path, Pdm) ->
- Self = self(),
- Epp = spawn(fun() -> server(Self, Name, Path, Pdm) end),
- epp_request(Epp).
+ internal_open([{name, Name}, {includes, Path}, {macros, Pdm}], #epp{}).
open(Name, File, StartLocation, Path, Pdm) ->
- Self = self(),
- Epp = spawn(fun() -> server(Self, Name, File, StartLocation,Path,Pdm) end),
- epp_request(Epp).
+ internal_open([{name, Name}, {includes, Path}, {macros, Pdm}],
+ #epp{file=File, pre_opened=true, location=StartLocation}).
+
+-spec open(Options) ->
+ {'ok', Epp} | {'ok', Epp, Extra} | {'error', ErrorDescriptor} when
+ Options :: [{'default_encoding', DefEncoding :: source_encoding()} |
+ {'includes', IncludePath :: [DirectoryName :: file:name()]} |
+ {'macros', PredefMacros :: macros()} |
+ {'name',FileName :: file:name()} |
+ 'extra'],
+ Epp :: epp_handle(),
+ Extra :: [{'encoding', source_encoding() | 'none'}],
+ ErrorDescriptor :: term().
+
+open(Options) ->
+ internal_open(Options, #epp{}).
+
+internal_open(Options, St) ->
+ case proplists:get_value(name, Options) of
+ undefined ->
+ erlang:error(badarg);
+ Name ->
+ Self = self(),
+ Epp = spawn(fun() -> server(Self, Name, Options, St) end),
+ case epp_request(Epp) of
+ {ok, Pid, Encoding} ->
+ case proplists:get_bool(extra, Options) of
+ true -> {ok, Pid, [{encoding, Encoding}]};
+ false -> {ok, Pid}
+ end;
+ Other ->
+ Other
+ end
+ end.
-spec close(Epp) -> 'ok' when
Epp :: epp_handle().
@@ -170,9 +214,6 @@ format_error({'NYI',What}) ->
io_lib:format("not yet implemented '~s'", [What]);
format_error(E) -> file:format_error(E).
-%% parse_file(FileName, IncludePath, [PreDefMacro]) ->
-%% {ok,[Form]} | {error,OpenError}
-
-spec parse_file(FileName, IncludePath, PredefMacros) ->
{'ok', [Form]} | {error, OpenError} when
FileName :: file:name(),
@@ -184,17 +225,40 @@ format_error(E) -> file:format_error(E).
OpenError :: file:posix() | badarg | system_limit.
parse_file(Ifile, Path, Predefs) ->
- case open(Ifile, Path, Predefs) of
+ parse_file(Ifile, [{includes, Path}, {macros, Predefs}]).
+
+-spec parse_file(FileName, Options) ->
+ {'ok', [Form]} | {'ok', [Form], Extra} | {error, OpenError} when
+ FileName :: file:name(),
+ Options :: [{'includes', IncludePath :: [DirectoryName :: file:name()]} |
+ {'macros', PredefMacros :: macros()} |
+ {'default_encoding', DefEncoding :: source_encoding()} |
+ 'extra'],
+ Form :: erl_parse:abstract_form() | {'error', ErrorInfo} | {'eof',Line},
+ Line :: erl_scan:line(),
+ ErrorInfo :: erl_scan:error_info() | erl_parse:error_info(),
+ Extra :: [{'encoding', source_encoding() | 'none'}],
+ OpenError :: file:posix() | badarg | system_limit.
+
+parse_file(Ifile, Options) ->
+ case internal_open([{name, Ifile} | Options], #epp{}) of
{ok,Epp} ->
Forms = parse_file(Epp),
close(Epp),
{ok,Forms};
+ {ok,Epp,Extra} ->
+ Forms = parse_file(Epp),
+ close(Epp),
+ {ok,Forms,Extra};
{error,E} ->
{error,E}
end.
-%% parse_file(Epp) ->
-%% [Form]
+-spec parse_file(Epp) -> [Form] when
+ Epp :: epp_handle(),
+ Form :: erl_parse:abstract_form() | {'error', ErrorInfo} | {'eof',Line},
+ Line :: erl_scan:line(),
+ ErrorInfo :: erl_scan:error_info() | erl_parse:error_info().
parse_file(Epp) ->
case parse_erl_form(Epp) of
@@ -219,8 +283,6 @@ parse_file(Epp) ->
[{eof,Location}]
end.
--define(DEFAULT_ENCODING, latin1).
-
-spec default_encoding() -> source_encoding().
default_encoding() ->
@@ -258,9 +320,16 @@ read_encoding(Name, Options) ->
File :: io:device(). % pid(); raw files don't work
set_encoding(File) ->
+ set_encoding(File, ?DEFAULT_ENCODING).
+
+-spec set_encoding(File, Default) -> source_encoding() | none when
+ Default :: source_encoding(),
+ File :: io:device(). % pid(); raw files don't work
+
+set_encoding(File, Default) ->
Encoding = read_encoding_from_file(File, true),
Enc = case Encoding of
- none -> default_encoding();
+ none -> Default;
Encoding -> Encoding
end,
ok = io:setopts(File, [{encoding, Enc}]),
@@ -446,35 +515,37 @@ restore_typed_record_fields([{attribute,La,type,{{record,Record},Fields,[]}}|
restore_typed_record_fields([Form|Forms]) ->
[Form|restore_typed_record_fields(Forms)].
-%% server(StarterPid, FileName, Path, PreDefMacros)
-
-server(Pid, Name, Path, Pdm) ->
+server(Pid, Name, Options, #epp{pre_opened=PreOpened}=St) ->
process_flag(trap_exit, true),
- case file:open(Name, [read]) of
- {ok,File} ->
- Location = 1,
- init_server(Pid, Name, File, Location, Path, Pdm, false);
- {error,E} ->
- epp_reply(Pid, {error,E})
+ case PreOpened of
+ false ->
+ case file:open(Name, [read]) of
+ {ok,File} ->
+ init_server(Pid, Name, Options, St#epp{file = File});
+ {error,E} ->
+ epp_reply(Pid, {error,E})
+ end;
+ true ->
+ init_server(Pid, Name, Options, St)
end.
-%% server(StarterPid, FileName, IoDevice, Location, Path, PreDefMacros)
-server(Pid, Name, File, AtLocation, Path, Pdm) ->
- process_flag(trap_exit, true),
- init_server(Pid, Name, File, AtLocation, Path, Pdm, true).
-
-init_server(Pid, Name, File, AtLocation, Path, Pdm, Pre) ->
+init_server(Pid, Name, Options, St0) ->
+ Pdm = proplists:get_value(macros, Options, []),
Ms0 = predef_macros(Name),
case user_predef(Pdm, Ms0) of
{ok,Ms1} ->
- _ = set_encoding(File),
- epp_reply(Pid, {ok,self()}),
+ #epp{file = File, location = AtLocation} = St0,
+ DefEncoding = proplists:get_value(default_encoding, Options,
+ ?DEFAULT_ENCODING),
+ Encoding = set_encoding(File, DefEncoding),
+ epp_reply(Pid, {ok,self(),Encoding}),
%% ensure directory of current source file is
%% first in path
- Path1 = [filename:dirname(Name) | Path],
- St = #epp{file=File, location=AtLocation, delta=0,
- name=Name, name2=Name, path=Path1, macs=Ms1,
- pre_opened = Pre},
+ Path = [filename:dirname(Name) |
+ proplists:get_value(includes, Options, [])],
+ St = St0#epp{delta=0, name=Name, name2=Name,
+ path=Path, macs=Ms1,
+ default_encoding=DefEncoding},
From = wait_request(St),
enter_file_reply(From, Name, AtLocation, AtLocation),
wait_req_scan(St);
@@ -600,9 +671,11 @@ enter_file2(NewF, Pname, From, St0, AtLocation) ->
%% the path) must be dropped, otherwise the path used within the current
%% file will depend on the order of file inclusions in the parent files
Path = [filename:dirname(Pname) | tl(St0#epp.path)],
- _ = set_encoding(NewF),
+ DefEncoding = St0#epp.default_encoding,
+ _ = set_encoding(NewF, DefEncoding),
#epp{file=NewF,location=Loc,name=Pname,name2=Pname,delta=0,
- sstk=[St0|St0#epp.sstk],path=Path,macs=Ms}.
+ sstk=[St0|St0#epp.sstk],path=Path,macs=Ms,
+ default_encoding=DefEncoding}.
enter_file_reply(From, Name, Location, AtLocation) ->
Attr = loc_attr(AtLocation),
@@ -640,11 +713,11 @@ leave_file(From, St) ->
Ms = dict:store({atom,'FILE'},
{none,[{string,CurrLoc,OldName2}]},
St#epp.macs),
- NextSt = OldSt#epp{sstk=Sts,macs=Ms},
+ NextSt = OldSt#epp{sstk=Sts,macs=Ms,uses=St#epp.uses},
enter_file_reply(From, OldName, CurrLoc, CurrLoc),
case OldName2 =:= OldName of
true ->
- From;
+ ok;
false ->
NFrom = wait_request(NextSt),
enter_file_reply(NFrom, OldName2, OldLoc,
@@ -1048,8 +1121,20 @@ skip_toks(From, St, [I|Sis]) ->
skip_toks(From, St#epp{location=Cl}, Sis);
{ok,_Toks,Cl} ->
skip_toks(From, St#epp{location=Cl}, [I|Sis]);
- {error,_E,Cl} ->
- skip_toks(From, St#epp{location=Cl}, [I|Sis]);
+ {error,E,Cl} ->
+ case E of
+ {_,file_io_server,invalid_unicode} ->
+ %% The compiler needs to know that there was
+ %% invalid unicode characters in the file
+ %% (and there is no point in continuing anyway
+ %% since io server process has terminated).
+ epp_reply(From, {error,E}),
+ leave_file(wait_request(St), St);
+ _ ->
+ %% Some other invalid token, such as a bad floating
+ %% point number. Just ignore it.
+ skip_toks(From, St#epp{location=Cl}, [I|Sis])
+ end;
{eof,Cl} ->
leave_file(From, St#epp{location=Cl,istk=[I|Sis]});
{error,_E} ->
@@ -1247,6 +1332,8 @@ macro_arg([{'case',Lc}|Toks], E, Arg) ->
macro_arg(Toks, ['end'|E], [{'case',Lc}|Arg]);
macro_arg([{'fun',Lc}|[{'(',_}|_]=Toks], E, Arg) ->
macro_arg(Toks, ['end'|E], [{'fun',Lc}|Arg]);
+macro_arg([{'fun',_}=Fun,{var,_,_}=Name|[{'(',_}|_]=Toks], E, Arg) ->
+ macro_arg(Toks, ['end'|E], [Name,Fun|Arg]);
macro_arg([{'receive',Lr}|Toks], E, Arg) ->
macro_arg(Toks, ['end'|E], [{'receive',Lr}|Arg]);
macro_arg([{'try',Lr}|Toks], E, Arg) ->
diff --git a/lib/stdlib/src/erl_compile.erl b/lib/stdlib/src/erl_compile.erl
index 8c3d59467b..caed4d41d6 100644
--- a/lib/stdlib/src/erl_compile.erl
+++ b/lib/stdlib/src/erl_compile.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1997-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1997-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -21,10 +21,12 @@
-include("erl_compile.hrl").
-include("file.hrl").
--export([compile_cmdline/1]).
+-export([compile_cmdline/0]).
-export_type([cmd_line_arg/0]).
+-define(STDERR, standard_error). %Macro to avoid misspellings.
+
%% Mapping from extension to {M,F} to run the correct compiler.
compiler(".erl") -> {compile, compile};
@@ -47,9 +49,10 @@ compiler(_) -> no.
-type cmd_line_arg() :: atom() | string().
--spec compile_cmdline([cmd_line_arg()]) -> no_return().
+-spec compile_cmdline() -> no_return().
-compile_cmdline(List) ->
+compile_cmdline() ->
+ List = init:get_plain_arguments(),
case compile(List) of
ok -> my_halt(0);
error -> my_halt(1);
@@ -63,86 +66,204 @@ my_halt(Reason) ->
compile(List) ->
process_flag(trap_exit, true),
- Pid = spawn_link(fun() -> compiler_runner(List) end),
+ Pid = spawn_link(compiler_runner(List)),
receive
{'EXIT', Pid, {compiler_result, Result}} ->
Result;
+ {'EXIT', Pid, {compiler_error, Error}} ->
+ io:put_chars(?STDERR, Error),
+ io:nl(?STDERR),
+ error;
{'EXIT', Pid, Reason} ->
- io:format("Runtime error: ~tp~n", [Reason]),
+ io:format(?STDERR, "Runtime error: ~tp~n", [Reason]),
error
end.
--spec compiler_runner([cmd_line_arg()]) -> no_return().
+-spec compiler_runner([cmd_line_arg()]) -> fun(() -> no_return()).
compiler_runner(List) ->
- %% We don't want the current directory in the code path.
- %% Remove it.
- Path = [D || D <- code:get_path(), D =/= "."],
- true = code:set_path(Path),
- exit({compiler_result, compile1(List)}).
+ fun() ->
+ %% We don't want the current directory in the code path.
+ %% Remove it.
+ Path = [D || D <- code:get_path(), D =/= "."],
+ true = code:set_path(Path),
+ exit({compiler_result, compile1(List)})
+ end.
%% Parses the first part of the option list.
-compile1(['@cwd', Cwd|Rest]) ->
- CwdL = atom_to_list(Cwd),
- compile1(Rest, CwdL, #options{outdir=CwdL, cwd=CwdL});
compile1(Args) ->
- %% From R13B02, the @cwd argument is optional.
{ok, Cwd} = file:get_cwd(),
- compile1(Args, Cwd, #options{outdir=Cwd, cwd=Cwd}).
+ compile1(Args, #options{outdir=Cwd,cwd=Cwd}).
%% Parses all options.
-compile1(['@i', Dir|Rest], Cwd, Opts) ->
+compile1(["--"|Files], Opts) ->
+ compile2(Files, Opts);
+compile1(["-"++Option|T], Opts) ->
+ parse_generic_option(Option, T, Opts);
+compile1(["+"++Option|Rest], Opts) ->
+ Term = make_term(Option),
+ Specific = Opts#options.specific,
+ compile1(Rest, Opts#options{specific=[Term|Specific]});
+compile1(Files, Opts) ->
+ compile2(Files, Opts).
+
+parse_generic_option("b"++Opt, T0, Opts) ->
+ {OutputType,T} = get_option("b", Opt, T0),
+ compile1(T, Opts#options{output_type=list_to_atom(OutputType)});
+parse_generic_option("D"++Opt, T0, #options{defines=Defs}=Opts) ->
+ {Val0,T} = get_option("D", Opt, T0),
+ {Key0,Val1} = split_at_equals(Val0, []),
+ Key = list_to_atom(Key0),
+ case Val1 of
+ [] ->
+ compile1(T, Opts#options{defines=[Key|Defs]});
+ Val2 ->
+ Val = make_term(Val2),
+ compile1(T, Opts#options{defines=[{Key,Val}|Defs]})
+ end;
+parse_generic_option("help", _, _Opts) ->
+ usage();
+parse_generic_option("I"++Opt, T0, #options{cwd=Cwd}=Opts) ->
+ {Dir,T} = get_option("I", Opt, T0),
AbsDir = filename:absname(Dir, Cwd),
- compile1(Rest, Cwd, Opts#options{includes=[AbsDir|Opts#options.includes]});
-compile1(['@outdir', Dir|Rest], Cwd, Opts) ->
+ compile1(T, Opts#options{includes=[AbsDir|Opts#options.includes]});
+parse_generic_option("M"++Opt, T0, #options{specific=Spec}=Opts) ->
+ case parse_dep_option(Opt, T0) of
+ error ->
+ error;
+ {SpecOpts,T} ->
+ compile1(T, Opts#options{specific=SpecOpts++Spec})
+ end;
+parse_generic_option("o"++Opt, T0, #options{cwd=Cwd}=Opts) ->
+ {Dir,T} = get_option("o", Opt, T0),
AbsName = filename:absname(Dir, Cwd),
case file_or_directory(AbsName) of
file ->
- compile1(Rest, Cwd, Opts#options{outfile=AbsName});
+ compile1(T, Opts#options{outfile=AbsName});
directory ->
- compile1(Rest, Cwd, Opts#options{outdir=AbsName})
+ compile1(T, Opts#options{outdir=AbsName})
end;
-compile1(['@d', Name|Rest], Cwd, Opts) ->
- Defines = Opts#options.defines,
- compile1(Rest, Cwd, Opts#options{defines=[Name|Defines]});
-compile1(['@dv', Name, Term|Rest], Cwd, Opts) ->
- Defines = Opts#options.defines,
- Value = make_term(atom_to_list(Term)),
- compile1(Rest, Cwd, Opts#options{defines=[{Name, Value}|Defines]});
-compile1(['@warn', Level0|Rest], Cwd, Opts) ->
- case catch list_to_integer(atom_to_list(Level0)) of
- Level when is_integer(Level) ->
- compile1(Rest, Cwd, Opts#options{warning=Level});
+parse_generic_option("O"++Opt, T, Opts) ->
+ case Opt of
+ "" ->
+ compile1(T, Opts#options{optimize=1});
_ ->
- compile1(Rest, Cwd, Opts)
+ Term = make_term(Opt),
+ compile1(T, Opts#options{optimize=Term})
end;
-compile1(['@verbose', false|Rest], Cwd, Opts) ->
- compile1(Rest, Cwd, Opts#options{verbose=false});
-compile1(['@verbose', true|Rest], Cwd, Opts) ->
- compile1(Rest, Cwd, Opts#options{verbose=true});
-compile1(['@optimize', Atom|Rest], Cwd, Opts) ->
- Term = make_term(atom_to_list(Atom)),
- compile1(Rest, Cwd, Opts#options{optimize=Term});
-compile1(['@option', Atom|Rest], Cwd, Opts) ->
- Term = make_term(atom_to_list(Atom)),
- Specific = Opts#options.specific,
- compile1(Rest, Cwd, Opts#options{specific=[Term|Specific]});
-compile1(['@output_type', OutputType|Rest], Cwd, Opts) ->
- compile1(Rest, Cwd, Opts#options{output_type=OutputType});
-compile1(['@files'|Rest], Cwd, Opts) ->
- Includes = lists:reverse(Opts#options.includes),
- compile2(Rest, Cwd, Opts#options{includes=Includes}).
-
-compile2(Files, Cwd, Opts) ->
- case {Opts#options.outfile, length(Files)} of
+parse_generic_option("v", T, Opts) ->
+ compile1(T, Opts#options{verbose=true});
+parse_generic_option("W"++Warn, T, #options{specific=Spec}=Opts) ->
+ case Warn of
+ "all" ->
+ compile1(T, Opts#options{warning=999});
+ "error" ->
+ compile1(T, Opts#options{specific=[warnings_as_errors|Spec]});
+ "" ->
+ compile1(T, Opts#options{warning=1});
+ _ ->
+ try list_to_integer(Warn) of
+ Level ->
+ compile1(T, Opts#options{warning=Level})
+ catch
+ error:badarg ->
+ usage()
+ end
+ end;
+parse_generic_option("E", T, #options{specific=Spec}=Opts) ->
+ compile1(T, Opts#options{specific=['E'|Spec]});
+parse_generic_option("P", T, #options{specific=Spec}=Opts) ->
+ compile1(T, Opts#options{specific=['P'|Spec]});
+parse_generic_option("S", T, #options{specific=Spec}=Opts) ->
+ compile1(T, Opts#options{specific=['S'|Spec]});
+parse_generic_option(Option, _T, _Opts) ->
+ io:format(?STDERR, "Unknown option: -~s\n", [Option]),
+ usage().
+
+parse_dep_option("", T) ->
+ {[makedep,{makedep_output,standard_io}],T};
+parse_dep_option("D", T) ->
+ {[makedep],T};
+parse_dep_option("F"++Opt, T0) ->
+ {File,T} = get_option("MF", Opt, T0),
+ {[makedep,{makedep_output,File}],T};
+parse_dep_option("G", T) ->
+ {[makedep_add_missing],T};
+parse_dep_option("P", T) ->
+ {[makedep_phony],T};
+parse_dep_option("Q"++Opt, T0) ->
+ {Target,T} = get_option("MT", Opt, T0),
+ {[makedep_quote_target,{makedep_target,Target}],T};
+parse_dep_option("T"++Opt, T0) ->
+ {Target,T} = get_option("MT", Opt, T0),
+ {[{makedep_target,Target}],T};
+parse_dep_option(Opt, _T) ->
+ io:format(?STDERR, "Unknown option: -M~s\n", [Opt]),
+ usage().
+
+usage() ->
+ H = [{"-b type","type of output file (e.g. beam)"},
+ {"-d","turn on debugging of erlc itself"},
+ {"-Dname","define name"},
+ {"-Dname=value","define name to have value"},
+ {"-help","shows this help text"},
+ {"-I path","where to search for include files"},
+ {"-M","generate a rule for make(1) describing the dependencies"},
+ {"-MF file","write the dependencies to 'file'"},
+ {"-MT target","change the target of the rule emitted by dependency "
+ "generation"},
+ {"-MQ target","same as -MT but quote characters special to make(1)"},
+ {"-MG","consider missing headers as generated files and add them to "
+ "the dependencies"},
+ {"-MP","add a phony target for each dependency"},
+ {"-MD","same as -M -MT file (with default 'file')"},
+ {"-o name","name output directory or file"},
+ {"-pa path","add path to the front of Erlang's code path"},
+ {"-pz path","add path to the end of Erlang's code path"},
+ {"-smp","compile using SMP emulator"},
+ {"-v","verbose compiler output"},
+ {"-Werror","make all warnings into errors"},
+ {"-W0","disable warnings"},
+ {"-Wnumber","set warning level to number"},
+ {"-Wall","enable all warnings"},
+ {"-W","enable warnings (default; same as -W1)"},
+ {"-E","generate listing of expanded code (Erlang compiler)"},
+ {"-S","generate assembly listing (Erlang compiler)"},
+ {"-P","generate listing of preprocessed code (Erlang compiler)"},
+ {"+term","pass the Erlang term unchanged to the compiler"}],
+ io:put_chars(?STDERR,
+ ["Usage: erlc [Options] file.ext ...\n",
+ "Options:\n",
+ [io_lib:format("~-14s ~s\n", [K,D]) || {K,D} <- H]]),
+ error.
+
+get_option(_Name, [], [[C|_]=Option|T]) when C =/= $- ->
+ {Option,T};
+get_option(_Name, [_|_]=Option, T) ->
+ {Option,T};
+get_option(Name, _, _) ->
+ exit({compiler_error,"No value given to -"++Name++" option"}).
+
+split_at_equals([$=|T], Acc) ->
+ {lists:reverse(Acc),T};
+split_at_equals([H|T], Acc) ->
+ split_at_equals(T, [H|Acc]);
+split_at_equals([], Acc) ->
+ {lists:reverse(Acc),[]}.
+
+compile2(Files, #options{cwd=Cwd,includes=Incl,outfile=Outfile}=Opts0) ->
+ Opts = Opts0#options{includes=lists:reverse(Incl)},
+ case {Outfile,length(Files)} of
{"", _} ->
compile3(Files, Cwd, Opts);
{[_|_], 1} ->
compile3(Files, Cwd, Opts);
{[_|_], _N} ->
- io:format("Output file name given, but more than one input file.~n"),
+ io:put_chars(?STDERR,
+ "Output file name given, "
+ "but more than one input file.\n"),
error
end.
@@ -170,23 +291,25 @@ compile3([], _Cwd, _Options) -> ok.
%% Invokes the appropriate compiler, depending on the file extension.
compile_file("", Input, _Output, _Options) ->
- io:format("File has no extension: ~ts~n", [Input]),
+ io:format(?STDERR, "File has no extension: ~ts~n", [Input]),
error;
compile_file(Ext, Input, Output, Options) ->
case compiler(Ext) of
no ->
- io:format("Unknown extension: '~ts'\n", [Ext]),
+ io:format(?STDERR, "Unknown extension: '~ts'\n", [Ext]),
error;
{M, F} ->
case catch M:F(Input, Output, Options) of
ok -> ok;
error -> error;
{'EXIT',Reason} ->
- io:format("Compiler function ~w:~w/3 failed:\n~p~n",
+ io:format(?STDERR,
+ "Compiler function ~w:~w/3 failed:\n~p~n",
[M,F,Reason]),
error;
Other ->
- io:format("Compiler function ~w:~w/3 returned:\n~p~n",
+ io:format(?STDERR,
+ "Compiler function ~w:~w/3 returned:\n~p~n",
[M,F,Other]),
error
end
@@ -215,10 +338,10 @@ make_term(Str) ->
case erl_parse:parse_term(Tokens ++ [{dot, 1}]) of
{ok, Term} -> Term;
{error, {_,_,Reason}} ->
- io:format("~ts: ~ts~n", [Reason, Str]),
+ io:format(?STDERR, "~ts: ~ts~n", [Reason, Str]),
throw(error)
end;
{error, {_,_,Reason}, _} ->
- io:format("~ts: ~ts~n", [Reason, Str]),
+ io:format(?STDERR, "~ts: ~ts~n", [Reason, Str]),
throw(error)
end.
diff --git a/lib/stdlib/src/erl_eval.erl b/lib/stdlib/src/erl_eval.erl
index ca6a4b5c58..639ddfc214 100644
--- a/lib/stdlib/src/erl_eval.erl
+++ b/lib/stdlib/src/erl_eval.erl
@@ -18,6 +18,9 @@
%%
-module(erl_eval).
+%% Guard is_map/1 is not yet supported in HiPE.
+-compile(no_native).
+
%% An evaluator for Erlang abstract syntax.
-export([exprs/2,exprs/3,exprs/4,expr/2,expr/3,expr/4,expr/5,
@@ -74,7 +77,7 @@
%% Only exprs/2 checks the command by calling erl_lint. The reason is
%% that if there is a function handler present, then it is possible
%% that there are valid constructs in Expression to be taken care of
-%% by a function handler but considerad errors by erl_lint.
+%% by a function handler but considered errors by erl_lint.
-spec(exprs(Expressions, Bindings) -> {value, Value, NewBindings} when
Expressions :: expressions(),
@@ -179,8 +182,12 @@ check_command(Es, Bs) ->
fun_data(F) when is_function(F) ->
case erlang:fun_info(F, module) of
{module,erl_eval} ->
- {env, [FBs,_FEf,_FLf,FCs]} = erlang:fun_info(F, env),
- {fun_data,FBs,FCs};
+ case erlang:fun_info(F, env) of
+ {env,[{FBs,_FLf,_FEf,FCs}]} ->
+ {fun_data,FBs,FCs};
+ {env,[{FBs,_FLf,_FEf,FCs,FName}]} ->
+ {named_fun_data,FBs,FName,FCs}
+ end;
_ ->
false
end;
@@ -235,6 +242,28 @@ expr({record,_,Name,_}, _Bs, _Lf, _Ef, _RBs) ->
erlang:raise(error, {undef_record,Name}, stacktrace());
expr({record,_,_,Name,_}, _Bs, _Lf, _Ef, _RBs) ->
erlang:raise(error, {undef_record,Name}, stacktrace());
+
+%% map
+expr({map,_,Binding,Es}, Bs0, Lf, Ef, RBs) ->
+ {value, Map0, Bs1} = expr(Binding, Bs0, Lf, Ef, none),
+ case Map0 of
+ #{} ->
+ {Vs,Bs2} = eval_map_fields(Es, Bs0, Lf, Ef),
+ Map1 = lists:foldl(fun ({map_assoc,K,V}, Mi) ->
+ maps:put(K, V, Mi);
+ ({map_exact,K,V}, Mi) ->
+ maps:update(K, V, Mi)
+ end, Map0, Vs),
+ ret_expr(Map1, merge_bindings(Bs2, Bs1), RBs);
+ _ ->
+ erlang:raise(error, {badarg,Map0}, stacktrace())
+ end;
+expr({map,_,Es}, Bs0, Lf, Ef, RBs) ->
+ {Vs,Bs} = eval_map_fields(Es, Bs0, Lf, Ef),
+ ret_expr(lists:foldl(fun
+ ({map_assoc,K,V}, Mi) -> maps:put(K,V,Mi)
+ end, maps:new(), Vs), Bs, RBs);
+
expr({block,_,Es}, Bs, Lf, Ef, RBs) ->
exprs(Es, Bs, Lf, Ef, RBs);
expr({'if',_,Cs}, Bs, Lf, Ef, RBs) ->
@@ -262,51 +291,99 @@ expr({'fun',Line,{clauses,Cs}} = Ex, Bs, Lf, Ef, RBs) ->
{Ex1, _} = hide_calls(Ex, 0),
{ok,Used} = erl_lint:used_vars([Ex1], Bs),
En = orddict:filter(fun(K,_V) -> member(K,Used) end, Bs),
+ Info = {En,Lf,Ef,Cs},
%% This is a really ugly hack!
F =
case length(element(3,hd(Cs))) of
- 0 -> fun () -> eval_fun(Cs, [], En, Lf, Ef) end;
- 1 -> fun (A) -> eval_fun(Cs, [A], En, Lf, Ef) end;
- 2 -> fun (A,B) -> eval_fun(Cs, [A,B], En, Lf, Ef) end;
- 3 -> fun (A,B,C) -> eval_fun(Cs, [A,B,C], En, Lf, Ef) end;
- 4 -> fun (A,B,C,D) -> eval_fun(Cs, [A,B,C,D], En, Lf, Ef) end;
- 5 -> fun (A,B,C,D,E) -> eval_fun(Cs, [A,B,C,D,E], En, Lf, Ef) end;
- 6 -> fun (A,B,C,D,E,F) -> eval_fun(Cs, [A,B,C,D,E,F], En, Lf, Ef) end;
- 7 -> fun (A,B,C,D,E,F,G) ->
- eval_fun(Cs, [A,B,C,D,E,F,G], En, Lf, Ef) end;
- 8 -> fun (A,B,C,D,E,F,G,H) ->
- eval_fun(Cs, [A,B,C,D,E,F,G,H], En, Lf, Ef) end;
- 9 -> fun (A,B,C,D,E,F,G,H,I) ->
- eval_fun(Cs, [A,B,C,D,E,F,G,H,I], En, Lf, Ef) end;
- 10 -> fun (A,B,C,D,E,F,G,H,I,J) ->
- eval_fun(Cs, [A,B,C,D,E,F,G,H,I,J], En, Lf, Ef) end;
- 11 -> fun (A,B,C,D,E,F,G,H,I,J,K) ->
- eval_fun(Cs, [A,B,C,D,E,F,G,H,I,J,K], En, Lf, Ef) end;
- 12 -> fun (A,B,C,D,E,F,G,H,I,J,K,L) ->
- eval_fun(Cs, [A,B,C,D,E,F,G,H,I,J,K,L], En, Lf, Ef) end;
- 13 -> fun (A,B,C,D,E,F,G,H,I,J,K,L,M) ->
- eval_fun(Cs, [A,B,C,D,E,F,G,H,I,J,K,L,M], En, Lf, Ef) end;
- 14 -> fun (A,B,C,D,E,F,G,H,I,J,K,L,M,N) ->
- eval_fun(Cs, [A,B,C,D,E,F,G,H,I,J,K,L,M,N], En, Lf, Ef) end;
- 15 -> fun (A,B,C,D,E,F,G,H,I,J,K,L,M,N,O) ->
- eval_fun(Cs, [A,B,C,D,E,F,G,H,I,J,K,L,M,N,O], En, Lf, Ef) end;
- 16 -> fun (A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P) ->
- eval_fun(Cs, [A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P], En, Lf, Ef) end;
- 17 -> fun (A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q) ->
- eval_fun(Cs, [A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q], En, Lf, Ef) end;
- 18 -> fun (A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R) ->
- eval_fun(Cs, [A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R], En, Lf, Ef) end;
- 19 -> fun (A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S) ->
- eval_fun(Cs, [A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S],
- En, Lf, Ef) end;
- 20 -> fun (A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T) ->
- eval_fun(Cs, [A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T],
- En, Lf, Ef) end;
+ 0 -> fun () -> eval_fun([], Info) end;
+ 1 -> fun (A) -> eval_fun([A], Info) end;
+ 2 -> fun (A,B) -> eval_fun([A,B], Info) end;
+ 3 -> fun (A,B,C) -> eval_fun([A,B,C], Info) end;
+ 4 -> fun (A,B,C,D) -> eval_fun([A,B,C,D], Info) end;
+ 5 -> fun (A,B,C,D,E) -> eval_fun([A,B,C,D,E], Info) end;
+ 6 -> fun (A,B,C,D,E,F) -> eval_fun([A,B,C,D,E,F], Info) end;
+ 7 -> fun (A,B,C,D,E,F,G) -> eval_fun([A,B,C,D,E,F,G], Info) end;
+ 8 -> fun (A,B,C,D,E,F,G,H) -> eval_fun([A,B,C,D,E,F,G,H], Info) end;
+ 9 -> fun (A,B,C,D,E,F,G,H,I) -> eval_fun([A,B,C,D,E,F,G,H,I], Info) end;
+ 10 -> fun (A,B,C,D,E,F,G,H,I,J) ->
+ eval_fun([A,B,C,D,E,F,G,H,I,J], Info) end;
+ 11 -> fun (A,B,C,D,E,F,G,H,I,J,K) ->
+ eval_fun([A,B,C,D,E,F,G,H,I,J,K], Info) end;
+ 12 -> fun (A,B,C,D,E,F,G,H,I,J,K,L) ->
+ eval_fun([A,B,C,D,E,F,G,H,I,J,K,L], Info) end;
+ 13 -> fun (A,B,C,D,E,F,G,H,I,J,K,L,M) ->
+ eval_fun([A,B,C,D,E,F,G,H,I,J,K,L,M], Info) end;
+ 14 -> fun (A,B,C,D,E,F,G,H,I,J,K,L,M,N) ->
+ eval_fun([A,B,C,D,E,F,G,H,I,J,K,L,M,N], Info) end;
+ 15 -> fun (A,B,C,D,E,F,G,H,I,J,K,L,M,N,O) ->
+ eval_fun([A,B,C,D,E,F,G,H,I,J,K,L,M,N,O], Info) end;
+ 16 -> fun (A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P) ->
+ eval_fun([A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P], Info) end;
+ 17 -> fun (A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q) ->
+ eval_fun([A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q], Info) end;
+ 18 -> fun (A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R) ->
+ eval_fun([A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R], Info) end;
+ 19 -> fun (A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S) ->
+ eval_fun([A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S], Info) end;
+ 20 -> fun (A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T) ->
+ eval_fun([A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T], Info) end;
_Other ->
erlang:raise(error, {'argument_limit',{'fun',Line,Cs}},
stacktrace())
end,
ret_expr(F, Bs, RBs);
+expr({named_fun,Line,Name,Cs} = Ex, Bs, Lf, Ef, RBs) ->
+ %% Save only used variables in the function environment.
+ %% {value,L,V} are hidden while lint finds used variables.
+ {Ex1, _} = hide_calls(Ex, 0),
+ {ok,Used} = erl_lint:used_vars([Ex1], Bs),
+ En = orddict:filter(fun(K,_V) -> member(K,Used) end, Bs),
+ Info = {En,Lf,Ef,Cs,Name},
+ %% This is a really ugly hack!
+ F =
+ case length(element(3,hd(Cs))) of
+ 0 -> fun RF() -> eval_named_fun([], RF, Info) end;
+ 1 -> fun RF(A) -> eval_named_fun([A], RF, Info) end;
+ 2 -> fun RF(A,B) -> eval_named_fun([A,B], RF, Info) end;
+ 3 -> fun RF(A,B,C) -> eval_named_fun([A,B,C], RF, Info) end;
+ 4 -> fun RF(A,B,C,D) -> eval_named_fun([A,B,C,D], RF, Info) end;
+ 5 -> fun RF(A,B,C,D,E) -> eval_named_fun([A,B,C,D,E], RF, Info) end;
+ 6 -> fun RF(A,B,C,D,E,F) -> eval_named_fun([A,B,C,D,E,F], RF, Info) end;
+ 7 -> fun RF(A,B,C,D,E,F,G) ->
+ eval_named_fun([A,B,C,D,E,F,G], RF, Info) end;
+ 8 -> fun RF(A,B,C,D,E,F,G,H) ->
+ eval_named_fun([A,B,C,D,E,F,G,H], RF, Info) end;
+ 9 -> fun RF(A,B,C,D,E,F,G,H,I) ->
+ eval_named_fun([A,B,C,D,E,F,G,H,I], RF, Info) end;
+ 10 -> fun RF(A,B,C,D,E,F,G,H,I,J) ->
+ eval_named_fun([A,B,C,D,E,F,G,H,I,J], RF, Info) end;
+ 11 -> fun RF(A,B,C,D,E,F,G,H,I,J,K) ->
+ eval_named_fun([A,B,C,D,E,F,G,H,I,J,K], RF, Info) end;
+ 12 -> fun RF(A,B,C,D,E,F,G,H,I,J,K,L) ->
+ eval_named_fun([A,B,C,D,E,F,G,H,I,J,K,L], RF, Info) end;
+ 13 -> fun RF(A,B,C,D,E,F,G,H,I,J,K,L,M) ->
+ eval_named_fun([A,B,C,D,E,F,G,H,I,J,K,L,M], RF, Info) end;
+ 14 -> fun RF(A,B,C,D,E,F,G,H,I,J,K,L,M,N) ->
+ eval_named_fun([A,B,C,D,E,F,G,H,I,J,K,L,M,N], RF, Info) end;
+ 15 -> fun RF(A,B,C,D,E,F,G,H,I,J,K,L,M,N,O) ->
+ eval_named_fun([A,B,C,D,E,F,G,H,I,J,K,L,M,N,O], RF, Info) end;
+ 16 -> fun RF(A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P) ->
+ eval_named_fun([A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P], RF, Info) end;
+ 17 -> fun RF(A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q) ->
+ eval_named_fun([A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q], RF, Info) end;
+ 18 -> fun RF(A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R) ->
+ eval_named_fun([A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R], RF, Info) end;
+ 19 -> fun RF(A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S) ->
+ eval_named_fun([A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S],
+ RF, Info) end;
+ 20 -> fun RF(A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T) ->
+ eval_named_fun([A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T],
+ RF, Info) end;
+ _Other ->
+ erlang:raise(error, {'argument_limit',{named_fun,Line,Name,Cs}},
+ stacktrace())
+ end,
+ ret_expr(F, Bs, RBs);
expr({call,_,{remote,_,{atom,_,qlc},{atom,_,q}},[{lc,_,_E,_Qs}=LC | As0]},
Bs0, Lf, Ef, RBs) when length(As0) =< 1 ->
%% No expansion or evaluation of module name or function name.
@@ -534,7 +611,7 @@ do_apply(Func, As, Bs0, Ef, RBs) ->
no_env
end,
case {Env,Ef} of
- {{env,[FBs, FEf, FLf, FCs]},_} ->
+ {{env,[{FBs,FLf,FEf,FCs}]},_} ->
%% If we are evaluting within another function body
%% (RBs =/= none), we return RBs when this function body
%% has been evalutated, otherwise we return Bs0, the
@@ -549,6 +626,17 @@ do_apply(Func, As, Bs0, Ef, RBs) ->
_ ->
erlang:raise(error, {badarity,{Func,As}},stacktrace())
end;
+ {{env,[{FBs,FLf,FEf,FCs,FName}]},_} ->
+ NRBs = if
+ RBs =:= none -> Bs0;
+ true -> RBs
+ end,
+ case {erlang:fun_info(Func, arity), length(As)} of
+ {{arity, Arity}, Arity} ->
+ eval_named_fun(FCs, As, FBs, FLf, FEf, FName, Func, NRBs);
+ _ ->
+ erlang:raise(error, {badarity,{Func,As}},stacktrace())
+ end;
{no_env,none} when RBs =:= value ->
%% Make tail recursive calls when possible.
apply(Func, As);
@@ -663,6 +751,24 @@ eval_filter(F, Bs0, Lf, Ef, CompFun, Acc) ->
end
end.
+%% eval_map_fields([Field], Bindings, LocalFunctionHandler,
+%% ExternalFuncHandler) ->
+%% {[{map_assoc | map_exact,Key,Value}],Bindings}
+
+eval_map_fields(Fs, Bs, Lf, Ef) ->
+ eval_map_fields(Fs, Bs, Lf, Ef, []).
+
+eval_map_fields([{map_field_assoc,_,K0,V0}|Fs], Bs0, Lf, Ef, Acc) ->
+ {value,K1,Bs1} = expr(K0, Bs0, Lf, Ef, none),
+ {value,V1,Bs2} = expr(V0, Bs1, Lf, Ef, none),
+ eval_map_fields(Fs, Bs2, Lf, Ef, [{map_assoc,K1,V1}|Acc]);
+eval_map_fields([{map_field_exact,_,K0,V0}|Fs], Bs0, Lf, Ef, Acc) ->
+ {value,K1,Bs1} = expr(K0, Bs0, Lf, Ef, none),
+ {value,V1,Bs2} = expr(V0, Bs1, Lf, Ef, none),
+ eval_map_fields(Fs, Bs2, Lf, Ef, [{map_exact,K1,V1}|Acc]);
+eval_map_fields([], Bs, _Lf, _Ef, Acc) ->
+ {lists:reverse(Acc),Bs}.
+
%% RBs is the bindings to return when the evalution of a function
%% (fun) has finished. If RBs =:= none, then the evalution took place
@@ -676,12 +782,12 @@ ret_expr(V, Bs, none) ->
ret_expr(V, _Bs, RBs) when is_list(RBs) ->
{value,V,RBs}.
-%% eval_fun(Clauses, Arguments, Bindings, LocalFunctionHandler,
-%% ExternalFunctionHandler) -> Value
+%% eval_fun(Arguments, {Bindings,LocalFunctionHandler,
+%% ExternalFunctionHandler,Clauses}) -> Value
%% This function is called when the fun is called from compiled code
%% or from apply.
-eval_fun(Cs, As, Bs0, Lf, Ef) ->
+eval_fun(As, {Bs0,Lf,Ef,Cs}) ->
eval_fun(Cs, As, Bs0, Lf, Ef, value).
eval_fun([{clause,_,H,G,B}|Cs], As, Bs0, Lf, Ef, RBs) ->
@@ -699,6 +805,27 @@ eval_fun([], As, _Bs, _Lf, _Ef, _RBs) ->
erlang:raise(error, function_clause,
[{?MODULE,'-inside-an-interpreted-fun-',As}|stacktrace()]).
+
+eval_named_fun(As, Fun, {Bs0,Lf,Ef,Cs,Name}) ->
+ eval_named_fun(Cs, As, Bs0, Lf, Ef, Name, Fun, value).
+
+eval_named_fun([{clause,_,H,G,B}|Cs], As, Bs0, Lf, Ef, Name, Fun, RBs) ->
+ Bs1 = add_binding(Name, Fun, Bs0),
+ case match_list(H, As, new_bindings(), Bs1) of
+ {match,Bsn} -> % The new bindings for the head
+ Bs2 = add_bindings(Bsn, Bs1), % which then shadow!
+ case guard(G, Bs2, Lf, Ef) of
+ true -> exprs(B, Bs2, Lf, Ef, RBs);
+ false -> eval_named_fun(Cs, As, Bs0, Lf, Ef, Name, Fun, RBs)
+ end;
+ nomatch ->
+ eval_named_fun(Cs, As, Bs0, Lf, Ef, Name, Fun, RBs)
+ end;
+eval_named_fun([], As, _Bs, _Lf, _Ef, _Name, _Fun, _RBs) ->
+ erlang:raise(error, function_clause,
+ [{?MODULE,'-inside-an-interpreted-fun-',As}|stacktrace()]).
+
+
%% expr_list(ExpressionList, Bindings)
%% expr_list(ExpressionList, Bindings, LocalFuncHandler)
%% expr_list(ExpressionList, Bindings, LocalFuncHandler, ExternalFuncHandler)
@@ -889,12 +1016,16 @@ guard0([], _Bs, _Lf, _Ef) -> true.
guard_test({call,L,{atom,Ln,F},As0}, Bs0, Lf, Ef) ->
TT = type_test(F),
G = {call,L,{atom,Ln,TT},As0},
- try {value,true,_} = expr(G, Bs0, Lf, Ef, none)
- catch error:_ -> {value,false,Bs0} end;
-guard_test({call,L,{remote,_Lr,{atom,_Lm,erlang},{atom,_Lf,_F}=T},As0},
+ expr_guard_test(G, Bs0, Lf, Ef);
+guard_test({call,L,{remote,Lr,{atom,Lm,erlang},{atom,Lf,F}},As0},
Bs0, Lf, Ef) ->
- guard_test({call,L,T,As0}, Bs0, Lf, Ef);
+ TT = type_test(F),
+ G = {call,L,{remote,Lr,{atom,Lm,erlang},{atom,Lf,TT}},As0},
+ expr_guard_test(G, Bs0, Lf, Ef);
guard_test(G, Bs0, Lf, Ef) ->
+ expr_guard_test(G, Bs0, Lf, Ef).
+
+expr_guard_test(G, Bs0, Lf, Ef) ->
try {value,true,_} = expr(G, Bs0, Lf, Ef, none)
catch error:_ -> {value,false,Bs0} end.
@@ -910,6 +1041,7 @@ type_test(port) -> is_port;
type_test(function) -> is_function;
type_test(binary) -> is_binary;
type_test(record) -> is_record;
+type_test(map) -> is_map;
type_test(Test) -> Test.
@@ -991,6 +1123,10 @@ match1({tuple,_,Elts}, Tuple, Bs, BBs)
match_tuple(Elts, Tuple, 1, Bs, BBs);
match1({tuple,_,_}, _, _Bs, _BBs) ->
throw(nomatch);
+match1({map,_,Fs}, #{}=Map, Bs, BBs) ->
+ match_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),
@@ -1034,6 +1170,18 @@ match_tuple([E|Es], Tuple, I, Bs0, BBs) ->
match_tuple([], _, _, Bs, _BBs) ->
{match,Bs}.
+match_map([{map_field_exact, _, K, V}|Fs], Map, Bs0, BBs) ->
+ Vm = try
+ {value, Ke, _} = expr(K, new_bindings()),
+ maps:get(Ke,Map)
+ catch error:_ ->
+ throw(nomatch)
+ end,
+ {match, Bs} = match1(V, Vm, Bs0, BBs),
+ match_map(Fs, Map, Bs, BBs);
+match_map([], _, Bs, _) ->
+ {match, Bs}.
+
%% match_list(PatternList, TermList, Bindings) ->
%% {match,NewBindings} | nomatch
%% Try to match a list of patterns against a list of terms with the
diff --git a/lib/stdlib/src/erl_expand_records.erl b/lib/stdlib/src/erl_expand_records.erl
index d05f630d8e..64a00acd88 100644
--- a/lib/stdlib/src/erl_expand_records.erl
+++ b/lib/stdlib/src/erl_expand_records.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2005-2012. All Rights Reserved.
+%% Copyright Ericsson AB 2005-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -38,6 +38,8 @@
checked_ra=[] % successfully accessed records
}).
+-define(REC_OFFSET, 100000000). % A hundred millions. Also in v3_core.
+
-spec(module(AbsForms, CompileOptions) -> AbsForms when
AbsForms :: [erl_parse:abstract_form()],
CompileOptions :: [compile:option()]).
@@ -132,15 +134,23 @@ pattern({cons,Line,H,T}, St0) ->
pattern({tuple,Line,Ps}, St0) ->
{TPs,St1} = pattern_list(Ps, St0),
{{tuple,Line,TPs},St1};
+pattern({map,Line,Ps}, St0) ->
+ {TPs,St1} = pattern_list(Ps, St0),
+ {{map,Line,TPs},St1};
+pattern({map_field_exact,Line,K0,V0}, St0) ->
+ {K,St1} = expr(K0, St0),
+ {V,St2} = pattern(V0, St1),
+ {{map_field_exact,Line,K,V},St2};
%%pattern({struct,Line,Tag,Ps}, St0) ->
%% {TPs,TPsvs,St1} = pattern_list(Ps, St0),
%% {{struct,Line,Tag,TPs},TPsvs,St1};
pattern({record_index,Line,Name,Field}, St) ->
{index_expr(Line, Field, Name, record_fields(Name, St)),St};
-pattern({record,Line,Name,Pfs}, St0) ->
+pattern({record,Line0,Name,Pfs}, St0) ->
Fs = record_fields(Name, St0),
{TMs,St1} = pattern_list(pattern_fields(Fs, Pfs), St0),
- {{tuple,Line,[{atom,Line,Name} | TMs]},St1};
+ Line = record_offset(Line0, St1),
+ {{tuple,Line,[{atom,Line0,Name} | TMs]},St1};
pattern({bin,Line,Es0}, St0) ->
{Es1,St1} = pattern_bin(Es0, St0),
{{bin,Line,Es1},St1};
@@ -301,14 +311,30 @@ expr({bc,Line,E0,Qs0}, St0) ->
expr({tuple,Line,Es0}, St0) ->
{Es1,St1} = expr_list(Es0, St0),
{{tuple,Line,Es1},St1};
+expr({map,Line,Es0}, St0) ->
+ {Es1,St1} = expr_list(Es0, St0),
+ {{map,Line,Es1},St1};
+expr({map,Line,Arg0,Es0}, St0) ->
+ {Arg1,St1} = expr(Arg0, St0),
+ {Es1,St2} = expr_list(Es0, St1),
+ {{map,Line,Arg1,Es1},St2};
+expr({map_field_assoc,Line,K0,V0}, St0) ->
+ {K,St1} = expr(K0, St0),
+ {V,St2} = expr(V0, St1),
+ {{map_field_assoc,Line,K,V},St2};
+expr({map_field_exact,Line,K0,V0}, St0) ->
+ {K,St1} = expr(K0, St0),
+ {V,St2} = expr(V0, St1),
+ {{map_field_exact,Line,K,V},St2};
%%expr({struct,Line,Tag,Es0}, Vs, St0) ->
%% {Es1,Esvs,Esus,St1} = expr_list(Es0, Vs, St0),
%% {{struct,Line,Tag,Es1},Esvs,Esus,St1};
expr({record_index,Line,Name,F}, St) ->
I = index_expr(Line, F, Name, record_fields(Name, St)),
expr(I, St);
-expr({record,Line,Name,Is}, St) ->
- expr({tuple,Line,[{atom,Line,Name} |
+expr({record,Line0,Name,Is}, St) ->
+ Line = record_offset(Line0, St),
+ expr({tuple,Line,[{atom,Line0,Name} |
record_inits(record_fields(Name, St), Is)]},
St);
expr({record_field,Line,R,Name,F}, St) ->
@@ -344,6 +370,9 @@ expr({'fun',_,{function,_M,_F,_A}}=Fun, St) ->
expr({'fun',Line,{clauses,Cs0}}, St0) ->
{Cs,St1} = clauses(Cs0, St0),
{{'fun',Line,{clauses,Cs}},St1};
+expr({named_fun,Line,Name,Cs0}, St0) ->
+ {Cs,St1} = clauses(Cs0, St0),
+ {{named_fun,Line,Name,Cs},St1};
expr({call,Line,{atom,_,is_record},[A,{atom,_,Name}]}, St) ->
record_test(Line, A, Name, St);
expr({call,Line,{remote,_,{atom,_,erlang},{atom,_,is_record}},
@@ -557,8 +586,9 @@ strict_get_record_field(Line, R, {atom,_,F}=Index, Name, St0) ->
I = index_expr(F, Fs, 2),
P = record_pattern(2, I, Var, length(Fs)+1, Line, [{atom,Line,Name}]),
NLine = neg_line(Line),
+ RLine = record_offset(NLine, St),
E = {'case',NLine,R,
- [{clause,NLine,[{tuple,NLine,P}],[],[Var]},
+ [{clause,NLine,[{tuple,RLine,P}],[],[Var]},
{clause,NLine,[{var,NLine,'_'}],[],
[{call,NLine,{remote,NLine,
{atom,NLine,erlang},
@@ -672,9 +702,10 @@ record_update(R, Name, Fs, Us0, St0) ->
record_match(R, Name, Lr, Fs, Us, St0) ->
{Ps,News,St1} = record_upd_fs(Fs, Us, St0),
NLr = neg_line(Lr),
+ RLine = record_offset(Lr, St1),
{{'case',Lr,R,
- [{clause,Lr,[{tuple,Lr,[{atom,Lr,Name} | Ps]}],[],
- [{tuple,Lr,[{atom,Lr,Name} | News]}]},
+ [{clause,Lr,[{tuple,RLine,[{atom,Lr,Name} | Ps]}],[],
+ [{tuple,RLine,[{atom,Lr,Name} | News]}]},
{clause,NLr,[{var,NLr,'_'}],[],
[call_error(NLr, {tuple,NLr,[{atom,NLr,badrecord},{atom,NLr,Name}]})]}
]},
@@ -703,6 +734,10 @@ record_setel(R, Name, Fs, Us0) ->
Lr = element(2, hd(Us)),
Wildcards = duplicate(length(Fs), {var,Lr,'_'}),
NLr = neg_line(Lr),
+ %% Note: calling record_offset() here is not necessary since it is
+ %% targeted at Dialyzer which always calls the compiler with
+ %% 'strict_record_updates' meaning that record_setel() will never
+ %% be called.
{'case',Lr,R,
[{clause,Lr,[{tuple,Lr,[{atom,Lr,Name} | Wildcards]}],[],
[foldr(fun ({I,Lf,Val}, Acc) ->
@@ -811,7 +846,7 @@ optimize_is_record(H0, G0, #exprec{compile=Opts}) ->
[] ->
{H0,G0};
Rs0 ->
- case lists:member(no_is_record_optimization, Opts) of
+ case lists:member(dialyzer, Opts) of % no_is_record_optimization
true ->
{H0,G0};
false ->
@@ -936,3 +971,10 @@ opt_remove_2(A, _) -> A.
neg_line(L) ->
erl_parse:set_line(L, fun(Line) -> -abs(Line) end).
+
+record_offset(L, St) ->
+ case lists:member(dialyzer, St#exprec.compile) of
+ true when L >= 0 -> L+?REC_OFFSET;
+ true when L < 0 -> L-?REC_OFFSET;
+ false -> L
+ end.
diff --git a/lib/stdlib/src/erl_internal.erl b/lib/stdlib/src/erl_internal.erl
index 378e629ac9..edfb097de0 100644
--- a/lib/stdlib/src/erl_internal.erl
+++ b/lib/stdlib/src/erl_internal.erl
@@ -70,6 +70,7 @@ guard_bif(bit_size, 1) -> true;
guard_bif(byte_size, 1) -> true;
guard_bif(element, 2) -> true;
guard_bif(self, 0) -> true;
+guard_bif(map_size, 1) -> true;
guard_bif(node, 0) -> true;
guard_bif(node, 1) -> true;
guard_bif(tuple_size, 1) -> true;
@@ -82,6 +83,7 @@ guard_bif(is_function, 1) -> true;
guard_bif(is_function, 2) -> true;
guard_bif(is_integer, 1) -> true;
guard_bif(is_list, 1) -> true;
+guard_bif(is_map, 1) -> true;
guard_bif(is_number, 1) -> true;
guard_bif(is_pid, 1) -> true;
guard_bif(is_port, 1) -> true;
@@ -113,6 +115,7 @@ new_type_test(is_function, 1) -> true;
new_type_test(is_function, 2) -> true;
new_type_test(is_integer, 1) -> true;
new_type_test(is_list, 1) -> true;
+new_type_test(is_map, 1) -> true;
new_type_test(is_number, 1) -> true;
new_type_test(is_pid, 1) -> true;
new_type_test(is_port, 1) -> true;
@@ -267,6 +270,7 @@ bif(bitstring_to_list, 1) -> true;
bif(byte_size, 1) -> true;
bif(check_old_code, 1) -> true;
bif(check_process_code, 2) -> true;
+bif(check_process_code, 3) -> true;
bif(date, 0) -> true;
bif(delete_module, 1) -> true;
bif(demonitor, 1) -> true;
@@ -286,6 +290,7 @@ bif(float_to_binary, 1) -> true;
bif(float_to_binary, 2) -> true;
bif(garbage_collect, 0) -> true;
bif(garbage_collect, 1) -> true;
+bif(garbage_collect, 2) -> true;
bif(get, 0) -> true;
bif(get, 1) -> true;
bif(get_keys, 1) -> true;
@@ -313,6 +318,7 @@ bif(is_function, 1) -> true;
bif(is_function, 2) -> true;
bif(is_integer, 1) -> true;
bif(is_list, 1) -> true;
+bif(is_map, 1) -> true;
bif(is_number, 1) -> true;
bif(is_pid, 1) -> true;
bif(is_port, 1) -> true;
@@ -333,6 +339,7 @@ bif(list_to_pid, 1) -> true;
bif(list_to_tuple, 1) -> true;
bif(load_module, 2) -> true;
bif(make_ref, 0) -> true;
+bif(map_size,1) -> true;
bif(max,2) -> true;
bif(min,2) -> true;
bif(module_loaded, 1) -> true;
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index f599881c07..39cc03cf7a 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -2,7 +2,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -80,13 +80,17 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->
-type fa() :: {atom(), arity()}. % function+arity
-type ta() :: {atom(), arity()}. % type+arity
+-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
imported = [], %Actually imported functions
- used_records=sets:new() :: set(), %Used record definitions
- used_types = dict:new() :: dict() %Used type definitions
+ used_records = sets:new() %Used record definitions
+ :: sets:set(atom()),
+ used_types = dict:new() %Used type definitions
+ :: dict:dict(ta(), line())
}).
%% Define the lint state record.
@@ -95,13 +99,17 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->
-record(lint, {state=start :: 'start' | 'attribute' | 'function',
module=[], %Module
behaviour=[], %Behaviour
- exports=gb_sets:empty() :: gb_set(), %Exports
- imports=[], %Imports
+ exports=gb_sets:empty() :: gb_sets:set(fa()),%Exports
+ imports=[] :: [fa()], %Imports, an orddict()
compile=[], %Compile flags
- records=dict:new() :: dict(), %Record definitions
- locals=gb_sets:empty() :: gb_set(), %All defined functions (prescanned)
- no_auto=gb_sets:empty() :: gb_set(), %Functions explicitly not autoimported
- defined=gb_sets:empty() :: gb_set(), %Defined fuctions
+ records=dict:new() %Record definitions
+ :: dict:dict(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
+ :: gb_sets:set(fa()) | 'all',
+ defined=gb_sets:empty() %Defined fuctions
+ :: gb_sets:set(fa()),
on_load=[] :: [fa()], %On-load function
on_load_line=0 :: line(), %Line for on_load
clashes=[], %Exported functions named as BIFs
@@ -116,12 +124,16 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->
%outside any fun or lc
xqlc= false :: boolean(), %true if qlc.hrl included
new = false :: boolean(), %Has user-defined 'new/N'
- called= [] :: [{fa(),line()}], %Called functions
+ called= [] :: [{fa(),line()}], %Called functions
usage = #usage{} :: #usage{},
- specs = dict:new() :: dict(), %Type specifications
- callbacks = dict:new() :: dict(), %Callback types
- types = dict:new() :: dict(), %Type definitions
- exp_types=gb_sets:empty():: gb_set() %Exported types
+ specs = dict:new() %Type specifications
+ :: dict:dict(mfa(), line()),
+ callbacks = dict:new() %Callback types
+ :: dict:dict(mfa(), line()),
+ types = dict:new() %Type definitions
+ :: dict:dict(ta(), #typeinfo{}),
+ exp_types=gb_sets:empty() %Exported types
+ :: gb_sets:set(ta())
}).
-type lint_state() :: #lint{}.
@@ -225,6 +237,10 @@ format_error({too_many_arguments,Arity}) ->
"maximum allowed is ~w", [Arity,?MAX_ARGUMENTS]);
%% --- patterns and guards ---
format_error(illegal_pattern) -> "illegal pattern";
+format_error(illegal_map_key) ->
+ "illegal map key";
+format_error({illegal_map_key_variable,K}) ->
+ io_lib:format("illegal use of variable ~w in map",[K]);
format_error(illegal_bin_pattern) ->
"binary patterns cannot be matched in parallel using '='";
format_error(illegal_expr) -> "illegal expression";
@@ -232,6 +248,9 @@ format_error({illegal_guard_local_call, {F,A}}) ->
io_lib:format("call to local/imported function ~w/~w is illegal in guard",
[F,A]);
format_error(illegal_guard_expr) -> "illegal guard expression";
+%% --- maps ---
+format_error(illegal_map_construction) ->
+ "only association operators '=>' are allowed in map construction";
%% --- records ---
format_error({undefined_record,T}) ->
io_lib:format("record ~w undefined", [T]);
@@ -281,6 +300,8 @@ format_error(utf_bittype_size_or_unit) ->
"neither size nor unit must be given for segments of type utf8/utf16/utf32";
format_error({bad_bitsize,Type}) ->
io_lib:format("bad ~s bit size", [Type]);
+format_error(unsized_binary_in_bin_gen_pattern) ->
+ "binary fields without size are not allowed in patterns of bit string generators";
%% --- behaviours ---
format_error({conflicting_behaviours,{Name,Arity},B,FirstL,FirstB}) ->
io_lib:format("conflicting behaviours - callback ~w/~w required by both '~p' "
@@ -310,10 +331,14 @@ format_error({undefined_type, {TypeName, Arity}}) ->
io_lib:format("type ~w~s undefined", [TypeName, gen_type_paren(Arity)]);
format_error({unused_type, {TypeName, Arity}}) ->
io_lib:format("type ~w~s is unused", [TypeName, gen_type_paren(Arity)]);
-format_error({new_builtin_type, {TypeName, Arity}}) ->
- io_lib:format("type ~w~s is a new builtin type; "
+%% format_error({new_builtin_type, {TypeName, Arity}}) ->
+%% io_lib:format("type ~w~s is a new builtin type; "
+%% "its (re)definition is allowed only until the next release",
+%% [TypeName, gen_type_paren(Arity)]);
+format_error({new_var_arity_type, TypeName}) ->
+ io_lib:format("type ~w is a new builtin type; "
"its (re)definition is allowed only until the next release",
- [TypeName, gen_type_paren(Arity)]);
+ [TypeName]);
format_error({builtin_type, {TypeName, Arity}}) ->
io_lib:format("type ~w~s is a builtin type; it cannot be redefined",
[TypeName, gen_type_paren(Arity)]);
@@ -337,9 +362,19 @@ format_error(spec_wrong_arity) ->
"spec has the wrong arity";
format_error(callback_wrong_arity) ->
"callback has the wrong arity";
-format_error({imported_predefined_type, Name}) ->
- io_lib:format("referring to built-in type ~w as a remote type; "
- "please take out the module name", [Name]);
+format_error({deprecated_builtin_type, {Name, Arity},
+ Replacement, Rel}) ->
+ UseS = case Replacement of
+ {Mod, NewName} ->
+ io_lib:format("use ~w:~w/~w", [Mod, NewName, Arity]);
+ {Mod, NewName, NewArity} ->
+ io_lib:format("use ~w:~w/~w or preferably ~w:~w/~w",
+ [Mod, NewName, Arity,
+ Mod, NewName, NewArity])
+ end,
+ io_lib:format("type ~w/~w is deprecated and will be "
+ "removed in ~s; use ~s",
+ [Name, Arity, Rel, UseS]);
format_error({not_exported_opaque, {TypeName, Arity}}) ->
io_lib:format("opaque type ~w~s is not exported",
[TypeName, gen_type_paren(Arity)]);
@@ -491,6 +526,9 @@ start(File, Opts) ->
{deprecated_function,
bool_option(warn_deprecated_function, nowarn_deprecated_function,
true, Opts)},
+ {deprecated_type,
+ bool_option(warn_deprecated_type, nowarn_deprecated_type,
+ true, Opts)},
{obsolete_guard,
bool_option(warn_obsolete_guard, nowarn_obsolete_guard,
true, Opts)},
@@ -842,8 +880,9 @@ behaviour_callbacks(Line, B, St0) ->
{[], St1}
end.
-behaviour_missing_callbacks([{{Line,B},Bfs}|T], #lint{exports=Exp}=St0) ->
- Missing = ordsets:subtract(ordsets:from_list(Bfs), gb_sets:to_list(Exp)),
+behaviour_missing_callbacks([{{Line,B},Bfs}|T], St0) ->
+ Exports = gb_sets:to_list(exports(St0)),
+ Missing = ordsets:subtract(ordsets:from_list(Bfs), Exports),
St = foldl(fun (F, S0) ->
add_warning(Line, {undefined_behaviour_func,F,B}, S0)
end, St0, Missing),
@@ -1007,9 +1046,10 @@ 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)} ||
- TA <- UTAs,
+ {T,_}=TA <- UTAs,
not dict:is_key(TA, Def),
- not is_default_type(TA)],
+ not is_default_type(TA),
+ not is_newly_introduced_var_arity_type(T)],
foldl(fun ({TA,L}, St) ->
add_error(L, {undefined_type,TA}, St)
end, St0, Undef).
@@ -1147,6 +1187,14 @@ export_type(Line, ETs, #lint{usage = Usage, exp_types = ETs0} = St0) ->
add_error(Line, {bad_export_type, ETs}, St0)
end.
+-spec exports(lint_state()) -> gb_sets:set(fa()).
+
+exports(#lint{compile = Opts, defined = Defs, exports = Es}) ->
+ case lists:member(export_all, Opts) of
+ true -> Defs;
+ false -> Es
+ end.
+
-type import() :: {module(), [fa()]} | module().
-spec import(line(), import(), lint_state()) -> lint_state().
@@ -1355,6 +1403,21 @@ pattern({cons,_Line,H,T}, Vt, Old, Bvt, St0) ->
{vtmerge_pat(Hvt, Tvt),vtmerge_pat(Bvt1,Bvt2),St2};
pattern({tuple,_Line,Ps}, Vt, Old, Bvt, St) ->
pattern_list(Ps, Vt, Old, Bvt, St);
+pattern({map,_Line,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,KP,VP}, {Psvt,Bvt0,St0}) ->
+ case is_valid_map_key(KP, pattern, St0) of
+ true ->
+ {Pvt,Bvt1,St1} = pattern(VP, Vt, Old, Bvt, St0),
+ {vtmerge_pat(Pvt, Psvt),vtmerge_pat(Bvt0, Bvt1), St1};
+ false ->
+ {Psvt,Bvt0,add_error(L, illegal_map_key, St0)};
+ {false,variable,Var} ->
+ {Psvt,Bvt0,add_error(L, {illegal_map_key_variable,Var}, St0)}
+ end
+ end, {[],[],St}, Ps);
%%pattern({struct,_Line,_Tag,Ps}, Vt, Old, Bvt, St) ->
%% pattern_list(Ps, Vt, Old, Bvt, St);
pattern({record_index,Line,Name,Field}, _Vt, _Old, _Bvt, St) ->
@@ -1742,6 +1805,12 @@ gexpr({cons,_Line,H,T}, Vt, St) ->
gexpr_list([H,T], Vt, St);
gexpr({tuple,_Line,Es}, Vt, St) ->
gexpr_list(Es, Vt, St);
+gexpr({map,_Line,Es}, Vt, St) ->
+ map_fields(Es, Vt, check_assoc_fields(Es, St), fun gexpr_list/3);
+gexpr({map,_Line,Src,Es}, Vt, St) ->
+ {Svt,St1} = gexpr(Src, Vt, St),
+ {Fvt,St2} = map_fields(Es, Vt, St1, fun gexpr_list/3),
+ {vtmerge(Svt, Fvt),St2};
gexpr({record_index,Line,Name,Field}, _Vt, St) ->
check_record(Line, Name, St,
fun (Dfs, St1) -> record_field(Field, Name, Dfs, St1) end );
@@ -1814,6 +1883,10 @@ gexpr({op,Line,Op,A}, Vt, St0) ->
true -> {Avt,St1};
false -> {Avt,add_error(Line, illegal_guard_expr, St1)}
end;
+gexpr({op,_,'andalso',L,R}, Vt, St) ->
+ gexpr_list([L,R], Vt, St);
+gexpr({op,_,'orelse',L,R}, Vt, St) ->
+ gexpr_list([L,R], Vt, St);
gexpr({op,Line,Op,L,R}, Vt, St0) ->
{Avt,St1} = gexpr_list([L,R], Vt, St0),
case is_gexpr_op(Op, 2) of
@@ -1851,7 +1924,7 @@ is_guard_test(Expression, Forms) ->
end, start(), RecordAttributes),
is_guard_test2(zip_file_and_line(Expression, "nofile"), St0#lint.records).
-%% is_guard_test2(Expression, RecordDefs :: dict()) -> boolean().
+%% is_guard_test2(Expression, RecordDefs :: dict:dict()) -> boolean().
is_guard_test2({call,Line,{atom,Lr,record},[E,A]}, RDs) ->
is_gexpr({call,Line,{atom,Lr,is_record},[E,A]}, RDs);
is_guard_test2({call,_Line,{atom,_La,Test},As}=Call, RDs) ->
@@ -1900,12 +1973,14 @@ is_gexpr({call,L,{tuple,Lt,[{atom,Lm,erlang},{atom,Lf,F}]},As}, RDs) ->
is_gexpr({call,L,{remote,Lt,{atom,Lm,erlang},{atom,Lf,F}},As}, RDs);
is_gexpr({op,_L,Op,A}, RDs) ->
is_gexpr_op(Op, 1) andalso is_gexpr(A, RDs);
+is_gexpr({op,_L,'andalso',A1,A2}, RDs) ->
+ is_gexpr_list([A1,A2], RDs);
+is_gexpr({op,_L,'orelse',A1,A2}, RDs) ->
+ is_gexpr_list([A1,A2], RDs);
is_gexpr({op,_L,Op,A1,A2}, RDs) ->
is_gexpr_op(Op, 2) andalso is_gexpr_list([A1,A2], RDs);
is_gexpr(_Other, _RDs) -> false.
-is_gexpr_op('andalso', 2) -> true;
-is_gexpr_op('orelse', 2) -> true;
is_gexpr_op(Op, A) ->
try erl_internal:op_type(Op, A) of
arith -> true;
@@ -1959,6 +2034,12 @@ expr({bc,_Line,E,Qs}, Vt, St) ->
handle_comprehension(E, Qs, Vt, St);
expr({tuple,_Line,Es}, Vt, St) ->
expr_list(Es, Vt, St);
+expr({map,_Line,Es}, Vt, St) ->
+ map_fields(Es, Vt, check_assoc_fields(Es, St), fun expr_list/3);
+expr({map,_Line,Src,Es}, Vt, St) ->
+ {Svt,St1} = expr(Src, Vt, St),
+ {Fvt,St2} = map_fields(Es, Vt, St1, fun expr_list/3),
+ {vtupdate(Svt, Fvt),St2};
expr({record_index,Line,Name,Field}, _Vt, St) ->
check_record(Line, Name, St,
fun (Dfs, St1) -> record_field(Field, Name, Dfs, St1) end);
@@ -2028,6 +2109,15 @@ expr({'fun',Line,Body}, Vt, St) ->
{Bvt, St1} = expr_list([M,F,A], Vt, St),
{vtupdate(Bvt, Vt),St1}
end;
+expr({named_fun,_,'_',Cs}, Vt, St) ->
+ fun_clauses(Cs, Vt, St);
+expr({named_fun,Line,Name,Cs}, Vt, St0) ->
+ Nvt0 = [{Name,{bound,unused,[Line]}}],
+ St1 = shadow_vars(Nvt0, Vt, 'named fun', St0),
+ Nvt1 = vtupdate(vtsubtract(Vt, Nvt0), Nvt0),
+ {Csvt,St2} = fun_clauses(Cs, Nvt1, St1),
+ {_,St3} = check_unused_vars(vtupdate(Csvt, Nvt0), [], St2),
+ {vtold(Csvt, Vt),St3};
expr({call,_Line,{atom,_Lr,is_record},[E,{atom,Ln,Name}]}, Vt, St0) ->
{Rvt,St1} = expr(E, Vt, St0),
{Rvt,exist_record(Ln, Name, St1)};
@@ -2157,6 +2247,26 @@ record_expr(Line, Rec, Vt, St0) ->
St1 = warn_invalid_record(Line, Rec, St0),
expr(Rec, Vt, St1).
+check_assoc_fields([{map_field_exact,Line,_,_}|Fs], St) ->
+ check_assoc_fields(Fs, add_error(Line, illegal_map_construction, St));
+check_assoc_fields([{map_field_assoc,_,_,_}|Fs], St) ->
+ check_assoc_fields(Fs, St);
+check_assoc_fields([], St) ->
+ St.
+
+map_fields([{Tag,Line,K,V}|Fs], Vt, St, F) when Tag =:= map_field_assoc;
+ Tag =:= map_field_exact ->
+ St1 = case is_valid_map_key(K, St) of
+ true -> St;
+ false -> add_error(Line, illegal_map_key, St);
+ {false,variable,Var} -> add_error(Line, {illegal_map_key_variable,Var}, St)
+ end,
+ {Pvt,St2} = F([K,V], Vt, St1),
+ {Vts,St3} = map_fields(Fs, Vt, St2, F),
+ {vtupdate(Pvt, Vts),St3};
+map_fields([], Vt, St, _) ->
+ {Vt,St}.
+
%% warn_invalid_record(Line, Record, State0) -> State
%% Adds warning if the record is invalid.
@@ -2180,6 +2290,7 @@ is_valid_record(Rec) ->
{lc, _, _, _} -> false;
{record_index, _, _, _} -> false;
{'fun', _, _} -> false;
+ {named_fun, _, _, _} -> false;
_ -> true
end.
@@ -2208,6 +2319,70 @@ is_valid_call(Call) ->
_ -> true
end.
+%% is_valid_map_key(K,St) -> true | false | {false, Var::atom()}
+%% check for value expression without variables
+
+is_valid_map_key(K,St) ->
+ is_valid_map_key(K,expr,St).
+is_valid_map_key(K,Ctx,St) ->
+ case expr(K,[],St) of
+ {[],_} ->
+ is_valid_map_key_value(K,Ctx);
+ {[Var|_],_} ->
+ {false,variable,element(1,Var)}
+ end.
+
+is_valid_map_key_value(K,Ctx) ->
+ case K of
+ {char,_,_} -> true;
+ {integer,_,_} -> true;
+ {float,_,_} -> true;
+ {string,_,_} -> true;
+ {nil,_} -> true;
+ {atom,_,_} -> true;
+ {cons,_,H,T} ->
+ is_valid_map_key_value(H,Ctx) andalso
+ is_valid_map_key_value(T,Ctx);
+ {tuple,_,Es} ->
+ foldl(fun(E,B) ->
+ B andalso is_valid_map_key_value(E,Ctx)
+ 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,Ctx) andalso foldl(fun
+ ({Tag,_,Ke,Ve},B) when Tag =:= map_field_assoc;
+ Tag =:= map_field_exact, Ctx =:= expr ->
+ B andalso is_valid_map_key_value(Ke,Ctx)
+ andalso is_valid_map_key_value(Ve,Ctx);
+ (_,_) -> false
+ end,true,Ps);
+ {map,_,Ps} ->
+ foldl(fun
+ ({Tag,_,Ke,Ve},B) when Tag =:= map_field_assoc;
+ Tag =:= map_field_exact, Ctx =:= expr ->
+ B andalso is_valid_map_key_value(Ke,Ctx)
+ andalso is_valid_map_key_value(Ve,Ctx);
+ (_,_) -> false
+ end, true, Ps);
+ {record,_,_,Fs} ->
+ foldl(fun
+ ({record_field,_,Ke,Ve},B) ->
+ B andalso is_valid_map_key_value(Ke,Ctx)
+ andalso is_valid_map_key_value(Ve,Ctx)
+ 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,Ctx)
+ end,true,Es);
+ _ -> false
+ 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.
@@ -2420,8 +2595,6 @@ find_field(_F, []) -> error.
%% Attr :: 'type' | 'opaque'
%% Checks that a type definition is valid.
--record(typeinfo, {attr, line}).
-
type_def(_Attr, _Line, {record, _RecName}, Fields, [], St0) ->
%% The record field names and such are checked in the record format.
%% We only need to check the types.
@@ -2438,32 +2611,46 @@ type_def(Attr, Line, TypeName, ProtoType, Args, St0) ->
CheckType = {type, -1, product, [ProtoType|Args]},
check_type(CheckType, St#lint{types=NewDefs})
end,
- case (dict:is_key(TypePair, TypeDefs) orelse is_var_arity_type(TypeName)) of
- true ->
- case is_default_type(TypePair) of
- true ->
- case is_newly_introduced_builtin_type(TypePair) of
- %% allow some types just for bootstrapping
- true ->
- Warn = {new_builtin_type, TypePair},
- St1 = add_warning(Line, Warn, St0),
- StoreType(St1);
- false ->
- add_error(Line, {builtin_type, TypePair}, St0)
- end;
- false -> add_error(Line, {redefine_type, TypePair}, St0)
- end;
- false ->
- St1 = case
- Attr =:= opaque andalso
- is_underspecified(ProtoType, Arity)
- of
- true ->
- Warn = {underspecified_opaque, TypePair},
- add_warning(Line, Warn, St0);
- false -> St0
- end,
- StoreType(St1)
+ case is_default_type(TypePair) of
+ true ->
+ case is_obsolete_builtin_type(TypePair) of
+ true -> StoreType(St0);
+ false -> add_error(Line, {builtin_type, TypePair}, St0)
+%% case is_newly_introduced_builtin_type(TypePair) of
+%% %% allow some types just for bootstrapping
+%% true ->
+%% Warn = {new_builtin_type, TypePair},
+%% St1 = add_warning(Line, Warn, St0),
+%% StoreType(St1);
+%% false ->
+%% add_error(Line, {builtin_type, TypePair}, St0)
+%% end
+ end;
+ false ->
+ case
+ dict:is_key(TypePair, TypeDefs) orelse
+ is_var_arity_type(TypeName)
+ of
+ true ->
+ case is_newly_introduced_var_arity_type(TypeName) of
+ true ->
+ Warn = {new_var_arity_type, TypeName},
+ add_warning(Line, Warn, St0);
+ false ->
+ add_error(Line, {redefine_type, TypePair}, St0)
+ end;
+ false ->
+ St1 = case
+ Attr =:= opaque andalso
+ is_underspecified(ProtoType, Arity)
+ of
+ true ->
+ Warn = {underspecified_opaque, TypePair},
+ add_warning(Line, Warn, St0);
+ false -> St0
+ end,
+ StoreType(St1)
+ end
end.
is_underspecified({type,_,term,[]}, 0) -> true;
@@ -2487,18 +2674,12 @@ check_type({paren_type, _L, [Type]}, SeenVars, St) ->
check_type(Type, SeenVars, St);
check_type({remote_type, L, [{atom, _, Mod}, {atom, _, Name}, Args]},
SeenVars, #lint{module=CurrentMod} = St) ->
- St1 =
- case is_default_type({Name, length(Args)})
- orelse is_var_arity_type(Name) of
- true -> add_error(L, {imported_predefined_type, Name}, St);
- false -> St
- end,
case Mod =:= CurrentMod of
- true -> check_type({type, L, Name, Args}, SeenVars, St1);
+ true -> check_type({type, L, Name, Args}, SeenVars, St);
false ->
lists:foldl(fun(T, {AccSeenVars, AccSt}) ->
check_type(T, AccSeenVars, AccSt)
- end, {SeenVars, St1}, Args)
+ end, {SeenVars, St}, Args)
end;
check_type({integer, _L, _}, SeenVars, St) -> {SeenVars, St};
check_type({atom, _L, _}, SeenVars, St) -> {SeenVars, St};
@@ -2528,6 +2709,13 @@ check_type({type, L, range, [From, To]}, SeenVars, St) ->
_ -> add_error(L, {type_syntax, range}, St)
end,
{SeenVars, St1};
+check_type({type, _L, map, any}, SeenVars, St) -> {SeenVars, St};
+check_type({type, _L, map, Pairs}, SeenVars, St) ->
+ lists:foldl(fun(Pair, {AccSeenVars, AccSt}) ->
+ check_type(Pair, AccSeenVars, AccSt)
+ end, {SeenVars, St}, Pairs);
+check_type({type, _L, map_field_assoc, Dom, Range}, SeenVars, St) ->
+ check_type({type, -1, product, [Dom, Range]}, SeenVars, St);
check_type({type, _L, tuple, any}, SeenVars, St) -> {SeenVars, St};
check_type({type, _L, any}, SeenVars, St) -> {SeenVars, St};
check_type({type, L, binary, [Base, Unit]}, SeenVars, St) ->
@@ -2549,14 +2737,35 @@ check_type({type, _L, product, Args}, SeenVars, St) ->
lists:foldl(fun(T, {AccSeenVars, AccSt}) ->
check_type(T, AccSeenVars, AccSt)
end, {SeenVars, St}, Args);
-check_type({type, La, TypeName, Args}, SeenVars, #lint{usage=Usage} = St) ->
+check_type({type, La, TypeName, Args}, SeenVars, St) ->
+ #lint{usage=Usage, module = Module, types=Types} = St,
Arity = length(Args),
+ TypePair = {TypeName, Arity},
St1 = case is_var_arity_type(TypeName) of
true -> St;
false ->
- OldUsed = Usage#usage.used_types,
- UsedTypes = dict:store({TypeName, Arity}, La, OldUsed),
- St#lint{usage=Usage#usage{used_types=UsedTypes}}
+ Obsolete = (is_warn_enabled(deprecated_type, St)
+ andalso obsolete_builtin_type(TypePair)),
+ IsObsolete =
+ case Obsolete of
+ {deprecated, Repl, _} when element(1, Repl) =/= Module ->
+ case dict:find(TypePair, Types) of
+ {ok, _} -> false;
+ error -> true
+ end;
+ _ -> false
+ end,
+ case IsObsolete of
+ true ->
+ {deprecated, Replacement, Rel} = Obsolete,
+ Tag = deprecated_builtin_type,
+ W = {Tag, TypePair, Replacement, Rel},
+ add_warning(La, W, St);
+ false ->
+ OldUsed = Usage#usage.used_types,
+ UsedTypes = dict:store(TypePair, La, OldUsed),
+ St#lint{usage=Usage#usage{used_types=UsedTypes}}
+ end
end,
check_type({type, -1, product, Args}, SeenVars, St1);
check_type(I, SeenVars, St) ->
@@ -2601,6 +2810,7 @@ check_record_types([], _Name, _DefFields, SeenVars, St, _SeenFields) ->
{SeenVars, St}.
is_var_arity_type(tuple) -> true;
+is_var_arity_type(map) -> true;
is_var_arity_type(product) -> true;
is_var_arity_type(union) -> true;
is_var_arity_type(record) -> true;
@@ -2663,20 +2873,32 @@ is_default_type({timeout, 0}) -> true;
is_default_type({var, 1}) -> true;
is_default_type(_) -> false.
-%% R13
-is_newly_introduced_builtin_type({arity, 0}) -> true;
-is_newly_introduced_builtin_type({array, 0}) -> true; % opaque
-is_newly_introduced_builtin_type({bitstring, 0}) -> true;
-is_newly_introduced_builtin_type({dict, 0}) -> true; % opaque
-is_newly_introduced_builtin_type({digraph, 0}) -> true; % opaque
-is_newly_introduced_builtin_type({gb_set, 0}) -> true; % opaque
-is_newly_introduced_builtin_type({gb_tree, 0}) -> true; % opaque
-is_newly_introduced_builtin_type({iodata, 0}) -> true;
-is_newly_introduced_builtin_type({queue, 0}) -> true; % opaque
-is_newly_introduced_builtin_type({set, 0}) -> true; % opaque
-%% R13B01
-is_newly_introduced_builtin_type({boolean, 0}) -> true;
-is_newly_introduced_builtin_type({Name, _}) when is_atom(Name) -> false.
+is_newly_introduced_var_arity_type(map) -> true;
+is_newly_introduced_var_arity_type(_) -> false.
+
+%% is_newly_introduced_builtin_type({Name, _}) when is_atom(Name) -> false.
+
+is_obsolete_builtin_type(TypePair) ->
+ obsolete_builtin_type(TypePair) =/= no.
+
+%% Obsolete in OTP 17.0.
+obsolete_builtin_type({array, 0}) ->
+ {deprecated, {array, array, 1}, "OTP 18.0"};
+obsolete_builtin_type({dict, 0}) ->
+ {deprecated, {dict, dict, 2}, "OTP 18.0"};
+obsolete_builtin_type({digraph, 0}) ->
+ {deprecated, {digraph, graph}, "OTP 18.0"};
+obsolete_builtin_type({gb_set, 0}) ->
+ {deprecated, {gb_sets, set, 1}, "OTP 18.0"};
+obsolete_builtin_type({gb_tree, 0}) ->
+ {deprecated, {gb_trees, tree, 2}, "OTP 18.0"};
+obsolete_builtin_type({queue, 0}) ->
+ {deprecated, {queue, queue, 1}, "OTP 18.0"};
+obsolete_builtin_type({set, 0}) ->
+ {deprecated, {sets, set, 1}, "OTP 18.0"};
+obsolete_builtin_type({tid, 0}) ->
+ {deprecated, {ets, tid}, "OTP 18.0"};
+obsolete_builtin_type({Name, A}) when is_atom(Name), is_integer(A) -> no.
%% spec_decl(Line, Fun, Types, State) -> State.
@@ -2882,7 +3104,8 @@ lc_quals([{generate,_Line,P,E} | Qs], Vt0, Uvt0, St0) ->
{Vt,Uvt,St} = handle_generator(P,E,Vt0,Uvt0,St0),
lc_quals(Qs, Vt, Uvt, St);
lc_quals([{b_generate,_Line,P,E} | Qs], Vt0, Uvt0, St0) ->
- {Vt,Uvt,St} = handle_generator(P,E,Vt0,Uvt0,St0),
+ St1 = handle_bitstring_gen_pat(P,St0),
+ {Vt,Uvt,St} = handle_generator(P,E,Vt0,Uvt0,St1),
lc_quals(Qs, Vt, Uvt, St);
lc_quals([F|Qs], Vt, Uvt, St0) ->
{Fvt,St1} = case is_guard_test2(F, St0#lint.records) of
@@ -2910,6 +3133,22 @@ handle_generator(P,E,Vt,Uvt,St0) ->
Vt3 = vtupdate(vtsubtract(Vt2, Binvt), Binvt),
{Vt3,NUvt,St5}.
+handle_bitstring_gen_pat({bin,_,Segments=[_|_]},St) ->
+ case lists:last(Segments) of
+ {bin_element,Line,{var,_,_},default,Flags} when is_list(Flags) ->
+ case member(binary, Flags) orelse member(bits, Flags)
+ orelse member(bitstring, Flags) of
+ true ->
+ add_error(Line, unsized_binary_in_bin_gen_pattern, St);
+ false ->
+ St
+ end;
+ _ ->
+ St
+ end;
+handle_bitstring_gen_pat(_,St) ->
+ St.
+
%% fun_clauses(Clauses, ImportVarTable, State) ->
%% {UsedVars, State}.
%% Fun's cannot export any variables.
@@ -3544,15 +3783,22 @@ is_imported_from_erlang(ImportSet,{Func,Arity}) ->
{ok,erlang} -> true;
_ -> false
end.
-%% Build set of functions where auto-import is explicitly supressed
+%% Build set of functions where auto-import is explicitly suppressed
auto_import_suppressed(CompileFlags) ->
- L0 = [ X || {no_auto_import,X} <- CompileFlags ],
- L1 = [ {Y,Z} || {Y,Z} <- lists:flatten(L0), is_atom(Y), is_integer(Z) ],
- gb_sets:from_list(L1).
-%% Predicate to find out if autoimport is explicitly supressed for a function
+ case lists:member(no_auto_import, CompileFlags) of
+ true ->
+ all;
+ false ->
+ L0 = [ X || {no_auto_import,X} <- CompileFlags ],
+ L1 = [ {Y,Z} || {Y,Z} <- lists:flatten(L0), is_atom(Y), is_integer(Z) ],
+ gb_sets:from_list(L1)
+ end.
+%% Predicate to find out if autoimport is explicitly suppressed for a function
+is_autoimport_suppressed(all,{_Func,_Arity}) ->
+ true;
is_autoimport_suppressed(NoAutoSet,{Func,Arity}) ->
gb_sets:is_element({Func,Arity},NoAutoSet).
-%% Predicate to find out if a function specific bif-clash supression (old deprecated) is present
+%% Predicate to find out if a function specific bif-clash suppression (old deprecated) is present
bif_clash_specifically_disabled(St,{F,A}) ->
Nowarn = nowarn_function(nowarn_bif_clash, St#lint.compile),
lists:member({F,A},Nowarn).
diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl
index 7145b0858f..1d4a2a1fef 100644
--- a/lib/stdlib/src/erl_parse.yrl
+++ b/lib/stdlib/src/erl_parse.yrl
@@ -2,7 +2,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -34,6 +34,7 @@ binary_comprehension
tuple
%struct
record_expr record_tuple record_field record_fields
+map_expr map_tuple map_field map_field_assoc map_field_exact map_fields map_key
if_expr if_clause if_clauses case_expr cr_clause cr_clauses receive_expr
fun_expr fun_clause fun_clauses atom_or_var integer_or_var
try_expr try_catch try_clause try_clauses
@@ -47,6 +48,7 @@ opt_bit_size_expr bit_size_expr opt_bit_type_list bit_type_list bit_type
top_type top_type_100 top_types type typed_expr typed_attr_val
type_sig type_sigs type_guard type_guards fun_type fun_type_100 binary_type
type_spec spec_fun typed_exprs typed_record_fields field_types field_type
+map_pair_types map_pair_type
bin_base_type bin_unit_type type_200 type_300 type_400 type_500.
Terminals
@@ -59,7 +61,7 @@ char integer float atom string var
'*' '/' 'div' 'rem' 'band' 'and'
'+' '-' 'bor' 'bxor' 'bsl' 'bsr' 'or' 'xor'
'++' '--'
-'==' '/=' '=<' '<' '>=' '>' '=:=' '=/=' '<='
+'==' '/=' '=<' '<' '>=' '>' '=:=' '=/=' '<=' '=>' ':='
'<<' '>>'
'!' '=' '::' '..' '...'
'spec' 'callback' % helper
@@ -154,6 +156,8 @@ type -> '[' ']' : {type, ?line('$1'), nil, []}.
type -> '[' top_type ']' : {type, ?line('$1'), list, ['$2']}.
type -> '[' top_type ',' '...' ']' : {type, ?line('$1'),
nonempty_list, ['$2']}.
+type -> '#' '{' '}' : {type, ?line('$1'), map, []}.
+type -> '#' '{' map_pair_types '}' : {type, ?line('$1'), map, '$3'}.
type -> '{' '}' : {type, ?line('$1'), tuple, []}.
type -> '{' top_types '}' : {type, ?line('$1'), tuple, '$2'}.
type -> '#' atom '{' '}' : {type, ?line('$1'), record, ['$2']}.
@@ -175,6 +179,10 @@ fun_type -> '(' top_types ')' '->' top_type
: {type, ?line('$1'), 'fun',
[{type, ?line('$1'), product, '$2'},'$5']}.
+map_pair_types -> map_pair_type : ['$1'].
+map_pair_types -> map_pair_type ',' map_pair_types : ['$1'|'$3'].
+map_pair_type -> top_type '=>' top_type : {type, ?line('$2'), map_field_assoc,'$1','$3'}.
+
field_types -> field_type : ['$1'].
field_types -> field_type ',' field_types : ['$1'|'$3'].
@@ -247,6 +255,7 @@ expr_500 -> expr_600 : '$1'.
expr_600 -> prefix_op expr_700 :
?mkop1('$1', '$2').
+expr_600 -> map_expr : '$1'.
expr_600 -> expr_700 : '$1'.
expr_700 -> function_call : '$1'.
@@ -327,6 +336,30 @@ tuple -> '{' exprs '}' : {tuple,?line('$1'),'$2'}.
%%struct -> atom tuple :
%% {struct,?line('$1'),element(3, '$1'),element(3, '$2')}.
+map_expr -> '#' map_tuple :
+ {map, ?line('$1'),'$2'}.
+map_expr -> expr_max '#' map_tuple :
+ {map, ?line('$2'),'$1','$3'}.
+map_expr -> map_expr '#' map_tuple :
+ {map, ?line('$2'),'$1','$3'}.
+
+map_tuple -> '{' '}' : [].
+map_tuple -> '{' map_fields '}' : '$2'.
+
+map_fields -> map_field : ['$1'].
+map_fields -> map_field ',' map_fields : ['$1' | '$3'].
+
+map_field -> map_field_assoc : '$1'.
+map_field -> map_field_exact : '$1'.
+
+map_field_assoc -> map_key '=>' expr :
+ {map_field_assoc,?line('$1'),'$1','$3'}.
+
+map_field_exact -> map_key ':=' expr :
+ {map_field_exact,?line('$1'),'$1','$3'}.
+
+map_key -> expr : '$1'.
+
%% N.B. This is called from expr_700.
%% N.B. Field names are returned as the complete object, even if they are
@@ -406,6 +439,9 @@ fun_clause -> argument_list clause_guard clause_body :
{Args,Pos} = '$1',
{clause,Pos,'fun',Args,'$2','$3'}.
+fun_clause -> var argument_list clause_guard clause_body :
+ {clause,element(2, '$1'),element(3, '$1'),element(1, '$2'),'$3','$4'}.
+
try_expr -> 'try' exprs 'of' cr_clauses try_catch :
build_try(?line('$1'),'$2','$4','$5').
try_expr -> 'try' exprs try_catch :
@@ -645,6 +681,8 @@ skip_paren(Type) ->
build_gen_type({atom, La, tuple}) ->
{type, La, tuple, any};
+build_gen_type({atom, La, map}) ->
+ {type, La, map, any};
build_gen_type({atom, La, Name}) ->
{type, La, Name, []}.
@@ -715,6 +753,9 @@ attribute_farity({cons,L,H,T}) ->
attribute_farity({tuple,L,Args0}) ->
Args = attribute_farity_list(Args0),
{tuple,L,Args};
+attribute_farity({map,L,Args0}) ->
+ Args = attribute_farity_map(Args0),
+ {map,L,Args};
attribute_farity({op,L,'/',{atom,_,_}=Name,{integer,_,_}=Arity}) ->
{tuple,L,[Name,Arity]};
attribute_farity(Other) -> Other.
@@ -722,6 +763,10 @@ attribute_farity(Other) -> Other.
attribute_farity_list(Args) ->
[attribute_farity(A) || A <- Args].
+%% It is not meaningful to have farity keys.
+attribute_farity_map(Args) ->
+ [{Op,L,K,attribute_farity(V)} || {Op,L,K,V} <- Args].
+
-spec error_bad_decl(integer(), attributes()) -> no_return().
error_bad_decl(L, S) ->
@@ -799,14 +844,23 @@ build_rule(Cs) ->
%% build_fun(Line, [Clause]) -> {'fun',Line,{clauses,[Clause]}}.
build_fun(Line, Cs) ->
+ Name = element(3, hd(Cs)),
Arity = length(element(4, hd(Cs))),
- {'fun',Line,{clauses,check_clauses(Cs, 'fun', Arity)}}.
+ CheckedCs = check_clauses(Cs, Name, Arity),
+ case Name of
+ 'fun' ->
+ {'fun',Line,{clauses,CheckedCs}};
+ Name ->
+ {named_fun,Line,Name,CheckedCs}
+ end.
check_clauses(Cs, Name, Arity) ->
- mapl(fun ({clause,L,N,As,G,B}) when N =:= Name, length(As) =:= Arity ->
- {clause,L,As,G,B};
- ({clause,L,_N,_As,_G,_B}) ->
- ret_err(L, "head mismatch") end, Cs).
+ [case C of
+ {clause,L,N,As,G,B} when N =:= Name, length(As) =:= Arity ->
+ {clause,L,As,G,B};
+ {clause,L,_N,_As,_G,_B} ->
+ ret_err(L, "head mismatch")
+ end || C <- Cs].
build_try(L,Es,Scs,{Ccs,As}) ->
{'try',L,Es,Scs,Ccs,As}.
@@ -816,17 +870,6 @@ ret_err(L, S) ->
{location,Location} = get_attribute(L, location),
return_error(Location, S).
-%% mapl(F,List)
-%% an alternative map which always maps from left to right
-%% and makes it possible to interrupt the mapping with throw on
-%% the first occurence from left as expected.
-%% can be removed when the jam machine (and all other machines)
-%% uses the standardized (Erlang 5.0) evaluation order (from left to right)
-mapl(F, [H|T]) ->
- V = F(H),
- [V | mapl(F,T)];
-mapl(_, []) ->
- [].
%% Convert between the abstract form of a term and a term.
@@ -850,6 +893,12 @@ normalise({cons,_,Head,Tail}) ->
[normalise(Head)|normalise(Tail)];
normalise({tuple,_,Args}) ->
list_to_tuple(normalise_list(Args));
+normalise({map,_,Pairs}=M) ->
+ maps:from_list(lists:map(fun
+ %% only allow '=>'
+ ({map_field_assoc,_,K,V}) -> {normalise(K),normalise(V)};
+ (_) -> erlang:error({badarg,M})
+ end, Pairs));
%% Special case for unary +/-.
normalise({op,_,'+',{char,_,I}}) -> I;
normalise({op,_,'+',{integer,_,I}}) -> I;
@@ -868,59 +917,65 @@ normalise_list([]) ->
Data :: term(),
AbsTerm :: abstract_expr().
abstract(T) ->
- abstract(T, 0, epp:default_encoding()).
+ abstract(T, 0, enc_func(epp:default_encoding())).
+
+-type encoding_func() :: fun((non_neg_integer()) -> boolean()).
%%% abstract/2 takes line and encoding options
-spec abstract(Data, Options) -> AbsTerm when
Data :: term(),
Options :: Line | [Option],
Option :: {line, Line} | {encoding, Encoding},
- Encoding :: latin1 | unicode | utf8,
+ Encoding :: 'latin1' | 'unicode' | 'utf8' | 'none' | encoding_func(),
Line :: erl_scan:line(),
AbsTerm :: abstract_expr().
abstract(T, Line) when is_integer(Line) ->
- abstract(T, Line, epp:default_encoding());
+ abstract(T, Line, enc_func(epp:default_encoding()));
abstract(T, Options) when is_list(Options) ->
Line = proplists:get_value(line, Options, 0),
Encoding = proplists:get_value(encoding, Options,epp:default_encoding()),
- abstract(T, Line, Encoding).
+ EncFunc = enc_func(Encoding),
+ abstract(T, Line, EncFunc).
-define(UNICODE(C),
- is_integer(C) andalso
- (C >= 0 andalso C < 16#D800 orelse
+ (C < 16#D800 orelse
C > 16#DFFF andalso C < 16#FFFE orelse
C > 16#FFFF andalso C =< 16#10FFFF)).
+enc_func(latin1) -> fun(C) -> C < 256 end;
+enc_func(unicode) -> fun(C) -> ?UNICODE(C) end;
+enc_func(utf8) -> fun(C) -> ?UNICODE(C) end;
+enc_func(none) -> none;
+enc_func(Fun) when is_function(Fun, 1) -> Fun;
+enc_func(Term) -> erlang:error({badarg, Term}).
+
abstract(T, L, _E) when is_integer(T) -> {integer,L,T};
abstract(T, L, _E) when is_float(T) -> {float,L,T};
abstract(T, L, _E) when is_atom(T) -> {atom,L,T};
abstract([], L, _E) -> {nil,L};
abstract(B, L, _E) when is_bitstring(B) ->
{bin, L, [abstract_byte(Byte, L) || Byte <- bitstring_to_list(B)]};
-abstract([C|T], L, unicode=E) when ?UNICODE(C) ->
- abstract_unicode_string(T, [C], L, E);
-abstract([C|T], L, utf8=E) when ?UNICODE(C) ->
- abstract_unicode_string(T, [C], L, E);
-abstract([C|T], L, latin1=E) when is_integer(C), 0 =< C, C < 256 ->
- abstract_string(T, [C], L, E);
-abstract([H|T], L, E) ->
+abstract([H|T], L, none=E) ->
{cons,L,abstract(H, L, E),abstract(T, L, E)};
+abstract(List, L, E) when is_list(List) ->
+ abstract_list(List, [], L, E);
abstract(Tuple, L, E) when is_tuple(Tuple) ->
- {tuple,L,abstract_list(tuple_to_list(Tuple), L, E)}.
-
-abstract_string([C|T], String, L, E) when is_integer(C), 0 =< C, C < 256 ->
- abstract_string(T, [C|String], L, E);
-abstract_string([], String, L, _E) ->
- {string, L, lists:reverse(String)};
-abstract_string(T, String, L, E) ->
- not_string(String, abstract(T, L, E), L, E).
-
-abstract_unicode_string([C|T], String, L, E) when ?UNICODE(C) ->
- abstract_unicode_string(T, [C|String], L, E);
-abstract_unicode_string([], String, L, _E) ->
+ {tuple,L,abstract_tuple_list(tuple_to_list(Tuple), L, E)};
+abstract(Map, L, E) when is_map(Map) ->
+ {map,L,abstract_map_fields(maps:to_list(Map),L,E)}.
+
+abstract_list([H|T], String, L, E) ->
+ case is_integer(H) andalso H >= 0 andalso E(H) of
+ true ->
+ abstract_list(T, [H|String], L, E);
+ false ->
+ AbstrList = {cons,L,abstract(H, L, E),abstract(T, L, E)},
+ not_string(String, AbstrList, L, E)
+ end;
+abstract_list([], String, L, _E) ->
{string, L, lists:reverse(String)};
-abstract_unicode_string(T, String, L, E) ->
+abstract_list(T, String, L, E) ->
not_string(String, abstract(T, L, E), L, E).
not_string([C|T], Result, L, E) ->
@@ -928,11 +983,14 @@ not_string([C|T], Result, L, E) ->
not_string([], Result, _L, _E) ->
Result.
-abstract_list([H|T], L, E) ->
- [abstract(H, L, E)|abstract_list(T, L, E)];
-abstract_list([], _L, _E) ->
+abstract_tuple_list([H|T], L, E) ->
+ [abstract(H, L, E)|abstract_tuple_list(T, L, E)];
+abstract_tuple_list([], _L, _E) ->
[].
+abstract_map_fields(Fs,L,E) ->
+ [{map_field_assoc,L,abstract(K,L,E),abstract(V,L,E)}||{K,V}<-Fs].
+
abstract_byte(Byte, L) when is_integer(Byte) ->
{bin_element, L, {integer, L, Byte}, default, default};
abstract_byte(Bits, L) ->
@@ -1050,3 +1108,5 @@ get_attribute(L, Name) ->
get_attributes(L) ->
erl_scan:attributes_info(L).
+
+%% vim: ft=erlang
diff --git a/lib/stdlib/src/erl_pp.erl b/lib/stdlib/src/erl_pp.erl
index 657cb5d34c..1fd6d2a8df 100644
--- a/lib/stdlib/src/erl_pp.erl
+++ b/lib/stdlib/src/erl_pp.erl
@@ -256,6 +256,10 @@ ltype({type,_Line,nonempty_list,[T]}) ->
{seq,$[,$],[$,],[ltype(T),leaf("...")]};
ltype({type,Line,nil,[]}) ->
lexpr({nil,Line}, 0, options(none));
+ltype({type,Line,map,any}) ->
+ simple_type({atom,Line,map}, []);
+ltype({type,_Line,map,Pairs}) ->
+ map_type(Pairs);
ltype({type,Line,tuple,any}) ->
simple_type({atom,Line,tuple}, []);
ltype({type,_Line,tuple,Ts}) ->
@@ -289,6 +293,23 @@ binary_type(I1, I2) ->
E2 = [[leaf("_:_*"),lexpr(I2, P, options(none))] || U],
{seq,'<<','>>',[$,],E1++E2}.
+map_type(Fs) ->
+ {first,[$#],map_pair_types(Fs)}.
+
+map_pair_types(Fs) ->
+ tuple_type(Fs, fun map_pair_type/1).
+
+map_pair_type({type,_Line,map_field_assoc,Ktype,Vtype}) ->
+ map_assoc_typed(ltype(Ktype), Vtype).
+
+map_assoc_typed(B, {type,_,union,Ts}) ->
+ {first,[B,$\s],{seq,[],[],[],map_assoc_union_type(Ts)}};
+map_assoc_typed(B, Type) ->
+ {list,[{cstep,[B," =>"],ltype(Type)}]}.
+
+map_assoc_union_type([T|Ts]) ->
+ [[leaf("=> "),ltype(T)] | ltypes(Ts, fun union_elem/1)].
+
record_type(Name, Fields) ->
{first,[record_name(Name)],field_types(Fields)}.
@@ -479,6 +500,15 @@ lexpr({record_field, _, Rec, F}, Prec, Opts) ->
{L,P,R} = inop_prec('.'),
El = [lexpr(Rec, L, Opts),$.,lexpr(F, R, Opts)],
maybe_paren(P, Prec, El);
+lexpr({map, _, Fs}, Prec, Opts) ->
+ {P,_R} = preop_prec('#'),
+ El = {first,leaf("#"),map_fields(Fs, Opts)},
+ maybe_paren(P, Prec, El);
+lexpr({map, _, Map, Fs}, Prec, Opts) ->
+ {L,P,_R} = inop_prec('#'),
+ Rl = lexpr(Map, L, Opts),
+ El = {first,[Rl,leaf("#")],map_fields(Fs, Opts)},
+ maybe_paren(P, Prec, El);
lexpr({block,_,Es}, _, Opts) ->
{list,[{step,'begin',body(Es, Opts)},'end']};
lexpr({'if',_,Cs}, _, Opts) ->
@@ -511,10 +541,17 @@ lexpr({'fun',_,{function,M,F,A}}, _Prec, Opts) ->
ArityItem = lexpr(A, Opts),
["fun ",NameItem,$:,CallItem,$/,ArityItem];
lexpr({'fun',_,{clauses,Cs}}, _Prec, Opts) ->
- {list,[{first,'fun',fun_clauses(Cs, Opts)},'end']};
+ {list,[{first,'fun',fun_clauses(Cs, Opts, unnamed)},'end']};
+lexpr({named_fun,_,Name,Cs}, _Prec, Opts) ->
+ {list,[{first,['fun', " "],fun_clauses(Cs, Opts, {named, Name})},'end']};
lexpr({'fun',_,{clauses,Cs},Extra}, _Prec, Opts) ->
{force_nl,fun_info(Extra),
- {list,[{first,'fun',fun_clauses(Cs, Opts)},'end']}};
+ {list,[{first,'fun',fun_clauses(Cs, Opts, unnamed)},'end']}};
+lexpr({named_fun,_,Name,Cs,Extra}, _Prec, Opts) ->
+ {force_nl,fun_info(Extra),
+ {list,[{first,['fun', " "],fun_clauses(Cs, Opts, {named, Name})},'end']}};
+lexpr({'query',_,Lc}, _Prec, Opts) ->
+ {list,[{step,leaf("query"),lexpr(Lc, 0, Opts)},'end']};
lexpr({call,_,{remote,_,{atom,_,M},{atom,_,F}=N}=Name,Args}, Prec, Opts) ->
case erl_internal:bif(M, F, length(Args)) of
true ->
@@ -664,6 +701,16 @@ record_field({typed_record_field,Field,Type}, Opts) ->
record_field({record_field,_,F}, Opts) ->
lexpr(F, 0, Opts).
+map_fields(Fs, Opts) ->
+ tuple(Fs, fun map_field/2, Opts).
+
+map_field({map_field_assoc,_,K,V}, Opts) ->
+ Pl = lexpr(K, 0, Opts),
+ {list,[{step,[Pl,leaf(" =>")],lexpr(V, 0, Opts)}]};
+map_field({map_field_exact,_,K,V}, Opts) ->
+ Pl = lexpr(K, 0, Opts),
+ {list,[{step,[Pl,leaf(" :=")],lexpr(V, 0, Opts)}]}.
+
list({cons,_,H,T}, Es, Opts) ->
list(T, [H|Es], Opts);
list({nil,_}, Es, Opts) ->
@@ -729,8 +776,13 @@ stack_backtrace(S, El, Opts) ->
%% fun_clauses(Clauses, Opts) -> [Char].
%% Print 'fun' clauses.
-fun_clauses(Cs, Opts) ->
- nl_clauses(fun fun_clause/2, [$;], Opts, Cs).
+fun_clauses(Cs, Opts, unnamed) ->
+ nl_clauses(fun fun_clause/2, [$;], Opts, Cs);
+fun_clauses(Cs, Opts, {named, Name}) ->
+ nl_clauses(fun (C, H) ->
+ {step,Gl,Bl} = fun_clause(C, H),
+ {step,[atom_to_list(Name),Gl],Bl}
+ end, [$;], Opts, Cs).
fun_clause({clause,_,A,G,B}, Opts) ->
El = args(A, Opts),
diff --git a/lib/stdlib/src/erl_scan.erl b/lib/stdlib/src/erl_scan.erl
index d988a4d8c7..6fd6bb888b 100644
--- a/lib/stdlib/src/erl_scan.erl
+++ b/lib/stdlib/src/erl_scan.erl
@@ -1,4 +1,3 @@
-%% -*- coding: utf-8 -*-
%%
%% %CopyrightBegin%
%%
@@ -570,7 +569,7 @@ scan1("++"++Cs, St, Line, Col, Toks) ->
tok2(Cs, St, Line, Col, Toks, "++", '++', 2);
scan1("+"=Cs, _St, Line, Col, Toks) ->
{more,{Cs,Col,Toks,Line,[],fun scan/6}};
-%% =:= =/= =< ==
+%% =:= =/= =< == =>
scan1("=:="++Cs, St, Line, Col, Toks) ->
tok2(Cs, St, Line, Col, Toks, "=:=", '=:=', 3);
scan1("=:"=Cs, _St, Line, Col, Toks) ->
@@ -581,6 +580,8 @@ scan1("=/"=Cs, _St, Line, Col, Toks) ->
{more,{Cs,Col,Toks,Line,[],fun scan/6}};
scan1("=<"++Cs, St, Line, Col, Toks) ->
tok2(Cs, St, Line, Col, Toks, "=<", '=<', 2);
+scan1("=>"++Cs, St, Line, Col, Toks) ->
+ tok2(Cs, St, Line, Col, Toks, "=>", '=>', 2);
scan1("=="++Cs, St, Line, Col, Toks) ->
tok2(Cs, St, Line, Col, Toks, "==", '==', 2);
scan1("="=Cs, _St, Line, Col, Toks) ->
@@ -595,6 +596,9 @@ scan1("||"++Cs, St, Line, Col, Toks) ->
tok2(Cs, St, Line, Col, Toks, "||", '||', 2);
scan1("|"=Cs, _St, Line, Col, Toks) ->
{more,{Cs,Col,Toks,Line,[],fun scan/6}};
+%% :=
+scan1(":="++Cs, St, Line, Col, Toks) ->
+ tok2(Cs, St, Line, Col, Toks, ":=", ':=', 2);
%% :-
scan1(":-"++Cs, St, Line, Col, Toks) ->
tok2(Cs, St, Line, Col, Toks, ":-", ':-', 2);
@@ -1071,7 +1075,7 @@ scan_number([$#|Cs]=Cs0, St, Line, Col, Toks, Ncs0) ->
Ncs = lists:reverse(Ncs0),
case catch list_to_integer(Ncs) of
B when B >= 2, B =< 1+$Z-$A+10 ->
- Bcs = ?STR(St, Ncs++[$#]),
+ Bcs = Ncs++[$#],
scan_based_int(Cs, St, Line, Col, Toks, {B,[],Bcs});
B ->
Len = length(Ncs),
@@ -1104,7 +1108,7 @@ scan_based_int(Cs, St, Line, Col, Toks, {B,Ncs0,Bcs}) ->
Ncs = lists:reverse(Ncs0),
case catch erlang:list_to_integer(Ncs, B) of
N when is_integer(N) ->
- tok3(Cs, St, Line, Col, Toks, integer, ?STR(St, Bcs++Ncs), N);
+ tok3(Cs, St, Line, Col, Toks, integer, Bcs++Ncs, N);
_ ->
Len = length(Bcs)+length(Ncs),
Ncol = incr_column(Col, Len),
diff --git a/lib/stdlib/src/erl_tar.erl b/lib/stdlib/src/erl_tar.erl
index 40ef6c8998..caa3276d09 100644
--- a/lib/stdlib/src/erl_tar.erl
+++ b/lib/stdlib/src/erl_tar.erl
@@ -22,7 +22,7 @@
%% Purpose: Unix tar (tape archive) utility.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
--export([create/2, create/3, extract/1, extract/2, table/1, table/2,
+-export([init/3, create/2, create/3, extract/1, extract/2, table/1, table/2,
open/2, close/1, add/3, add/4,
t/1, tt/1, format_error/1]).
@@ -30,10 +30,16 @@
-record(add_opts,
{read_info, % Fun to use for read file/link info.
+ chunk_size = 0, % For file reading when sending to sftp. 0=do not chunk
verbose = false :: boolean()}). % Verbose on/off.
%% Opens a tar archive.
+init(UsrHandle, AccessMode, Fun) when is_function(Fun,2) ->
+ {ok, {AccessMode,{tar_descriptor,UsrHandle,Fun}}}.
+
+%%%================================================================
+%%% The open function with friends is to keep the file and binary api of this module
open(Name, Mode) ->
case open_mode(Mode) of
{ok, Access, Raw, Opts} ->
@@ -45,31 +51,38 @@ open(Name, Mode) ->
open1({binary,Bin}, read, _Raw, Opts) ->
case file:open(Bin, [ram,binary,read]) of
{ok,File} ->
- case Opts of
- [compressed] -> ram_file:uncompress(File);
- [] -> ok
- end,
- {ok,{read,File}};
+ _ = [ram_file:uncompress(File) || Opts =:= [compressed]],
+ init(File,read,file_fun());
Error ->
Error
end;
open1({file, Fd}, read, _Raw, _Opts) ->
- {ok, {read, Fd}};
+ init(Fd, read, file_fun());
open1(Name, Access, Raw, Opts) ->
case file:open(Name, Raw ++ [binary, Access|Opts]) of
{ok, File} ->
- {ok, {Access, File}};
+ init(File, Access, file_fun());
{error, Reason} ->
{error, {Name, Reason}}
end.
+file_fun() ->
+ fun(write, {Fd,Data}) -> file:write(Fd, Data);
+ (position, {Fd,Pos}) -> file:position(Fd, Pos);
+ (read2, {Fd,Size}) -> file:read(Fd,Size);
+ (close, Fd) -> file:close(Fd)
+ end.
+
+%%% End of file and binary api (except for open_mode/1 downwards
+%%%================================================================
+
%% Closes a tar archive.
close({read, File}) ->
- ok = file:close(File);
+ ok = do_close(File);
close({write, File}) ->
PadResult = pad_file(File),
- ok = file:close(File),
+ ok = do_close(File),
PadResult;
close(_) ->
{error, einval}.
@@ -78,7 +91,6 @@ close(_) ->
add(File, Name, Options) ->
add(File, Name, Name, Options).
-
add({write, File}, Name, NameInArchive, Options) ->
Opts = #add_opts{read_info=fun(F) -> file:read_link_info(F) end},
add1(File, Name, NameInArchive, add_opts(Options, Opts));
@@ -91,6 +103,8 @@ add_opts([dereference|T], Opts) ->
add_opts(T, Opts#add_opts{read_info=fun(F) -> file:read_file_info(F) end});
add_opts([verbose|T], Opts) ->
add_opts(T, Opts#add_opts{verbose=true});
+add_opts([{chunks,N}|T], Opts) ->
+ add_opts(T, Opts#add_opts{chunk_size=N});
add_opts([_|T], Opts) ->
add_opts(T, Opts);
add_opts([], Opts) ->
@@ -324,16 +338,46 @@ add1(TarFile, Name, NameInArchive, Opts) ->
{error, {Name, Reason}}
end.
+add1(Tar, Name, Header, chunked, Options) ->
+ add_verbose(Options, "a ~ts [chunked ", [Name]),
+ try
+ ok = do_write(Tar, Header),
+ {ok,D} = file:open(Name, [read,binary]),
+ {ok,NumBytes} = add_read_write_chunks(D, Tar, Options#add_opts.chunk_size, 0, Options),
+ _ = file:close(D),
+ ok = do_write(Tar, padding(NumBytes,?record_size))
+ of
+ ok ->
+ add_verbose(Options, "~n", []),
+ ok
+ catch
+ error:{badmatch,{error,Error}} ->
+ add_verbose(Options, "~n", []),
+ {error,{Name,Error}}
+ end;
add1(Tar, Name, Header, Bin, Options) ->
add_verbose(Options, "a ~ts~n", [Name]),
- file:write(Tar, [Header, Bin, padding(byte_size(Bin), ?record_size)]).
+ do_write(Tar, [Header, Bin, padding(byte_size(Bin), ?record_size)]).
+
+add_read_write_chunks(D, Tar, ChunkSize, SumNumBytes, Options) ->
+ case file:read(D, ChunkSize) of
+ {ok,Bin} ->
+ ok = do_write(Tar, Bin),
+ add_verbose(Options, ".", []),
+ add_read_write_chunks(D, Tar, ChunkSize, SumNumBytes+byte_size(Bin), Options);
+ eof ->
+ add_verbose(Options, "]", []),
+ {ok,SumNumBytes};
+ Other ->
+ Other
+ end.
add_directory(TarFile, DirName, NameInArchive, Info, Options) ->
case file:list_dir(DirName) of
{ok, []} ->
add_verbose(Options, "a ~ts~n", [DirName]),
Header = create_header(NameInArchive, Info),
- file:write(TarFile, Header);
+ do_write(TarFile, Header);
{ok, Files} ->
Add = fun (File) ->
add1(TarFile,
@@ -384,7 +428,12 @@ to_octal(Int, Count, Result) ->
to_octal(Int div 8, Count-1, [Int rem 8 + $0|Result]).
to_string(Str0, Count) ->
- Str = list_to_binary(Str0),
+ Str = case file:native_name_encoding() of
+ utf8 ->
+ unicode:characters_to_binary(Str0);
+ latin1 ->
+ list_to_binary(Str0)
+ end,
case byte_size(Str) of
Size when Size < Count ->
[Str|zeroes(Count-Size)];
@@ -394,10 +443,18 @@ to_string(Str0, Count) ->
%% Pads out end of file.
pad_file(File) ->
- {ok,Position} = file:position(File, {cur,0}),
- %% There must be at least one empty record at the end of the file.
- Zeros = zeroes(?block_size - (Position rem ?block_size)),
- file:write(File, Zeros).
+ {ok,Position} = do_position(File, {cur,0}),
+ %% There must be at least two zero records at the end.
+ Fill = case ?block_size - (Position rem ?block_size) of
+ Fill0 when Fill0 < 2*?record_size ->
+ %% We need to another block here to ensure that there
+ %% are at least two zero records at the end.
+ Fill0 + ?block_size;
+ Fill0 ->
+ %% Large enough.
+ Fill0
+ end,
+ do_write(File, zeroes(Fill)).
split_filename(Name) when length(Name) =< ?th_name_len ->
{"", Name};
@@ -475,27 +532,36 @@ read_opts([_|Rest], Opts) ->
read_opts([], Opts) ->
Opts.
+foldl_read({AccessMode,TD={tar_descriptor,_UsrHandle,_AccessFun}}, Fun, Accu, Opts) ->
+ case AccessMode of
+ read ->
+ foldl_read0(TD, Fun, Accu, Opts);
+ _ ->
+ {error,{read_mode_expected,AccessMode}}
+ end;
foldl_read(TarName, Fun, Accu, Opts) ->
case open(TarName, [read|Opts#read_opts.open_mode]) of
{ok, {read, File}} ->
- Result =
- case catch foldl_read1(Fun, Accu, File, Opts) of
- {'EXIT', Reason} ->
- exit(Reason);
- {error, {Reason, Format, Args}} ->
- read_verbose(Opts, Format, Args),
- {error, Reason};
- {error, Reason} ->
- {error, Reason};
- Ok ->
- Ok
- end,
- ok = file:close(File),
+ Result = foldl_read0(File, Fun, Accu, Opts),
+ ok = do_close(File),
Result;
Error ->
Error
end.
+foldl_read0(File, Fun, Accu, Opts) ->
+ case catch foldl_read1(Fun, Accu, File, Opts) of
+ {'EXIT', Reason} ->
+ exit(Reason);
+ {error, {Reason, Format, Args}} ->
+ read_verbose(Opts, Format, Args),
+ {error, Reason};
+ {error, Reason} ->
+ {error, Reason};
+ Ok ->
+ Ok
+ end.
+
foldl_read1(Fun, Accu0, File, Opts) ->
case get_header(File) of
eof ->
@@ -549,7 +615,7 @@ check_extract(Name, #read_opts{files=Files}) ->
ordsets:is_element(Name, Files).
get_header(File) ->
- case file:read(File, ?record_size) of
+ case do_read(File, ?record_size) of
eof ->
throw({error,eof});
{ok, Bin} when is_binary(Bin) ->
@@ -611,7 +677,22 @@ typeflag(Bin) ->
%% Get the name of the file from the prefix and name fields of the
%% tar header.
-get_name(Bin) ->
+get_name(Bin0) ->
+ List0 = get_name_raw(Bin0),
+ case file:native_name_encoding() of
+ utf8 ->
+ Bin = list_to_binary(List0),
+ case unicode:characters_to_list(Bin) of
+ {error,_,_} ->
+ List0;
+ List when is_list(List) ->
+ List
+ end;
+ latin1 ->
+ List0
+ end.
+
+get_name_raw(Bin) ->
Name = from_string(Bin, ?th_name, ?th_name_len),
case binary_to_list(Bin, ?th_prefix+1, ?th_prefix+1) of
[0] ->
@@ -665,7 +746,7 @@ get_element(File, #tar_header{size = 0}) ->
skip_to_next(File),
{ok,<<>>};
get_element(File, #tar_header{size = Size}) ->
- case file:read(File, Size) of
+ case do_read(File, Size) of
{ok,Bin}=Res when byte_size(Bin) =:= Size ->
skip_to_next(File),
Res;
@@ -855,7 +936,7 @@ skip(File, Size) ->
%% Note: There is no point in handling failure to get the current position
%% in the file. If it doesn't work, something serious is wrong.
Amount = ((Size + ?record_size - 1) div ?record_size) * ?record_size,
- {ok,_} = file:position(File, {cur, Amount}),
+ {ok,_} = do_position(File, {cur, Amount}),
ok.
%% Skips to the next record in the file.
@@ -863,9 +944,9 @@ skip(File, Size) ->
skip_to_next(File) ->
%% Note: There is no point in handling failure to get the current position
%% in the file. If it doesn't work, something serious is wrong.
- {ok, Position} = file:position(File, {cur, 0}),
+ {ok, Position} = do_position(File, {cur, 0}),
NewPosition = ((Position + ?record_size - 1) div ?record_size) * ?record_size,
- {ok,NewPosition} = file:position(File, NewPosition),
+ {ok,NewPosition} = do_position(File, NewPosition),
ok.
%% Prints the message on if the verbose option is given.
@@ -891,6 +972,9 @@ posix_to_erlang_time(Sec) ->
read_file_and_info(Name, Opts) ->
ReadInfo = Opts#add_opts.read_info,
case ReadInfo(Name) of
+ {ok,Info} when Info#file_info.type =:= regular,
+ Opts#add_opts.chunk_size>0 ->
+ {ok,chunked,Info};
{ok,Info} when Info#file_info.type =:= regular ->
case file:read_file(Name) of
{ok,Bin} ->
@@ -937,3 +1021,12 @@ open_mode([], Access, Raw, Opts) ->
{ok, Access, Raw, Opts};
open_mode(_, _, _, _) ->
{error, einval}.
+
+%%%================================================================
+do_write({tar_descriptor,UsrHandle,Fun}, Data) -> Fun(write,{UsrHandle,Data}).
+
+do_position({tar_descriptor,UsrHandle,Fun}, Pos) -> Fun(position,{UsrHandle,Pos}).
+
+do_read({tar_descriptor,UsrHandle,Fun}, Len) -> Fun(read2,{UsrHandle,Len}).
+
+do_close({tar_descriptor,UsrHandle,Fun}) -> Fun(close,UsrHandle).
diff --git a/lib/stdlib/src/error_logger_tty_h.erl b/lib/stdlib/src/error_logger_tty_h.erl
index ad5891f191..e92142d154 100644
--- a/lib/stdlib/src/error_logger_tty_h.erl
+++ b/lib/stdlib/src/error_logger_tty_h.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2012. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2013. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -54,7 +54,7 @@ init([]) ->
handle_event({_Type, GL, _Msg}, State) when node(GL) =/= node() ->
{ok, State};
handle_event(Event, State) ->
- write_event(tag_event(Event),io),
+ ok = write_event(tag_event(Event),io),
{ok, State}.
handle_info({'EXIT', User, _Reason}, {User, PrevHandler}) ->
@@ -66,10 +66,10 @@ handle_info({'EXIT', User, _Reason}, {User, PrevHandler}) ->
PrevHandler, go_back}
end;
handle_info({emulator, GL, Chars}, State) when node(GL) == node() ->
- write_event(tag_event({emulator, GL, Chars}),io),
+ ok = write_event(tag_event({emulator, GL, Chars}),io),
{ok, State};
handle_info({emulator, noproc, Chars}, State) ->
- write_event(tag_event({emulator, noproc, Chars}),io),
+ ok = write_event(tag_event({emulator, noproc, Chars}),io),
{ok, State};
handle_info(_, State) ->
{ok, State}.
@@ -99,10 +99,11 @@ set_group_leader() ->
tag_event(Event) ->
{erlang:universaltime(), Event}.
+%% IOMOd is always 'io'
write_events(Events,IOMod) -> write_events1(lists:reverse(Events),IOMod).
write_events1([Event|Es],IOMod) ->
- write_event(Event,IOMod),
+ ok = write_event(Event,IOMod),
write_events1(Es,IOMod);
write_events1([],_IOMod) ->
ok.
diff --git a/lib/stdlib/src/escript.erl b/lib/stdlib/src/escript.erl
index fea718541d..6bd0eb8a22 100644
--- a/lib/stdlib/src/escript.erl
+++ b/lib/stdlib/src/escript.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2007-2013. All Rights Reserved.
+%% Copyright Ericsson AB 2007-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -59,7 +59,6 @@
file:filename()
| {file:filename(), binary()}
| {file:filename(), binary(), file:file_info()}.
--type zip_create_option() :: term().
-type section() ::
shebang
| {shebang, shebang() | default | undefined}
@@ -68,8 +67,8 @@
| {emu_args, emu_args() | undefined}
| {source, file:filename() | binary()}
| {beam, file:filename() | binary()}
- | {archive, file:filename() | binary()}
- | {archive, [zip_file()], [zip_create_option()]}.
+ | {archive, zip:filename() | binary()}
+ | {archive, [zip_file()], [zip:create_option()]}.
%%-----------------------------------------------------------------------
@@ -289,6 +288,8 @@ start(EscriptOptions) ->
my_halt(127)
end.
+-spec parse_and_run(_, _, _) -> no_return().
+
parse_and_run(File, Args, Options) ->
CheckOnly = lists:member("s", Options),
{Source, Module, FormsOrBin, HasRecs, Mode} =
@@ -727,6 +728,8 @@ epp_parse_file2(Epp, S, Forms, Parsed) ->
%% Evaluate script
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+-spec debug(_, _, _) -> no_return().
+
debug(Module, AbsMod, Args) ->
case hidden_apply(debugger, debugger, start, []) of
{ok, _} ->
@@ -742,6 +745,8 @@ debug(Module, AbsMod, Args) ->
fatal("Cannot start the debugger")
end.
+-spec run(_, _) -> no_return().
+
run(Module, Args) ->
try
Module:main(Args),
@@ -751,6 +756,8 @@ run(Module, Args) ->
fatal(format_exception(Class, Reason))
end.
+-spec interpret(_, _, _, _) -> no_return().
+
interpret(Forms, HasRecs, File, Args) ->
%% Basic validation before execution
case erl_lint:module(Forms) of
@@ -771,9 +778,11 @@ interpret(Forms, HasRecs, File, Args) ->
ArgsA = erl_parse:abstract(Args, 0),
Call = {call,0,{atom,0,main},[ArgsA]},
try
- erl_eval:expr(Call,
- erl_eval:new_bindings(),
- {value,fun(I, J) -> code_handler(I, J, Dict, File) end}),
+ _ = erl_eval:expr(Call,
+ erl_eval:new_bindings(),
+ {value,fun(I, J) ->
+ code_handler(I, J, Dict, File)
+ end}),
my_halt(0)
catch
Class:Reason ->
diff --git a/lib/stdlib/src/ets.erl b/lib/stdlib/src/ets.erl
index 77c8029f59..93c4f59896 100644
--- a/lib/stdlib/src/ets.erl
+++ b/lib/stdlib/src/ets.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -53,10 +53,8 @@
| {tab(),integer(),integer(),binary(),list(),integer()}
| {tab(),_,_,integer(),binary(),list(),integer(),integer()}.
-%% a similar definition is also in erl_types
-opaque tid() :: integer().
-%% these ones are also defined in erl_bif_types
-type match_pattern() :: atom() | tuple().
-type match_spec() :: [{match_pattern(), [_], [_]}].
@@ -507,7 +505,7 @@ fun2ms(ShellFun) when is_function(ShellFun) ->
Else ->
Else
end;
- false ->
+ _ ->
exit({badarg,{?MODULE,fun2ms,
[function,called,with,real,'fun',
should,be,transformed,with,
@@ -719,7 +717,7 @@ tab2file(Tab, File) ->
tab2file(Tab, File, Options) ->
try
{ok, FtOptions} = parse_ft_options(Options),
- file:delete(File),
+ _ = file:delete(File),
case file:read_file_info(File) of
{error, enoent} -> ok;
_ -> throw(eaccess)
@@ -750,14 +748,18 @@ tab2file(Tab, File, Options) ->
{fun(Oldstate,Termlist) ->
{NewState,BinList} =
md5terms(Oldstate,Termlist),
- disk_log:blog_terms(Name,BinList),
- NewState
+ case disk_log:blog_terms(Name,BinList) of
+ ok -> NewState;
+ {error, Reason2} -> throw(Reason2)
+ end
end,
erlang:md5_init()};
false ->
{fun(_,Termlist) ->
- disk_log:log_terms(Name,Termlist),
- true
+ case disk_log:log_terms(Name,Termlist) of
+ ok -> true;
+ {error, Reason2} -> throw(Reason2)
+ end
end,
true}
end,
@@ -792,16 +794,16 @@ tab2file(Tab, File, Options) ->
disk_log:close(Name)
catch
throw:TReason ->
- disk_log:close(Name),
- file:delete(File),
+ _ = disk_log:close(Name),
+ _ = file:delete(File),
throw(TReason);
exit:ExReason ->
- disk_log:close(Name),
- file:delete(File),
+ _ = disk_log:close(Name),
+ _ = file:delete(File),
exit(ExReason);
error:ErReason ->
- disk_log:close(Name),
- file:delete(File),
+ _ = disk_log:close(Name),
+ _ = file:delete(File),
erlang:raise(error,ErReason,erlang:get_stacktrace())
end
catch
@@ -892,25 +894,32 @@ file2tab(File, Opts) ->
try
{ok,Verify,TabArg} = parse_f2t_opts(Opts,false,[]),
Name = make_ref(),
- {ok, Major, Minor, FtOptions, MD5State, FullHeader, DLContext} =
+ {ok, Name} =
case disk_log:open([{name, Name},
{file, File},
{mode, read_only}]) of
{ok, Name} ->
- get_header_data(Name,Verify);
+ {ok, Name};
{repaired, Name, _,_} -> %Uh? cannot happen?
case Verify of
true ->
- disk_log:close(Name),
+ _ = disk_log:close(Name),
throw(badfile);
false ->
- get_header_data(Name,Verify)
+ {ok, Name}
end;
{error, Other1} ->
throw({read_error, Other1});
Other2 ->
throw(Other2)
end,
+ {ok, Major, Minor, FtOptions, MD5State, FullHeader, DLContext} =
+ try get_header_data(Name, Verify)
+ catch
+ badfile ->
+ _ = disk_log:close(Name),
+ throw(badfile)
+ end,
try
if
Major > ?MAJOR_F2T_VERSION ->
@@ -974,7 +983,7 @@ file2tab(File, Opts) ->
erlang:raise(error,ErReason,erlang:get_stacktrace())
end
after
- disk_log:close(Name)
+ _ = disk_log:close(Name)
end
catch
throw:TReason2 ->
@@ -1293,20 +1302,30 @@ named_table(false) -> [].
tabfile_info(File) when is_list(File) ; is_atom(File) ->
try
Name = make_ref(),
- {ok, Major, Minor, _FtOptions, _MD5State, FullHeader, _DLContext} =
+ {ok, Name} =
case disk_log:open([{name, Name},
{file, File},
{mode, read_only}]) of
{ok, Name} ->
- get_header_data(Name,false);
+ {ok, Name};
{repaired, Name, _,_} -> %Uh? cannot happen?
- get_header_data(Name,false);
+ {ok, Name};
{error, Other1} ->
throw({read_error, Other1});
Other2 ->
throw(Other2)
end,
- disk_log:close(Name),
+ {ok, Major, Minor, _FtOptions, _MD5State, FullHeader, _DLContext} =
+ try get_header_data(Name, false)
+ catch
+ badfile ->
+ _ = disk_log:close(Name),
+ throw(badfile)
+ end,
+ case disk_log:close(Name) of
+ ok -> ok;
+ {error, Reason} -> throw(Reason)
+ end,
{value, N} = lists:keysearch(name, 1, FullHeader),
{value, Type} = lists:keysearch(type, 1, FullHeader),
{value, P} = lists:keysearch(protection, 1, FullHeader),
@@ -1594,13 +1613,18 @@ choice(Height, Width, P, Mode, Tab, Key, Turn, Opos) ->
end.
get_line(P, Default) ->
- case io:get_line(P) of
+ case line_string(io:get_line(P)) of
"\n" ->
Default;
L ->
L
end.
+%% If the standard input is set to binary mode
+%% convert it to a list so we can properly match.
+line_string(Binary) when is_binary(Binary) -> unicode:characters_to_list(Binary);
+line_string(Other) -> Other.
+
nonl(S) -> string:strip(S, right, $\n).
print_number(Tab, Key, Num) ->
diff --git a/lib/stdlib/src/eval_bits.erl b/lib/stdlib/src/eval_bits.erl
index e49cbc1fd1..75fe2c00c7 100644
--- a/lib/stdlib/src/eval_bits.erl
+++ b/lib/stdlib/src/eval_bits.erl
@@ -192,7 +192,7 @@ 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),
+ 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).
@@ -380,20 +380,25 @@ make_bit_type(_Line, Size, Type0) -> %Size evaluates to an integer or 'all'
{error,Reason} -> error(Reason)
end.
-match_check_size(Mfun, {var,_,V}, Bs) ->
+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) ->
+match_check_size(_, {atom,_,all}, _Bs, true) ->
ok;
-match_check_size(_, {atom,_,undefined}, _Bs) ->
+match_check_size(_, {atom,_,all}, _Bs, false) ->
+ throw(invalid);
+match_check_size(_, {atom,_,undefined}, _Bs, _AllowAll) ->
ok;
-match_check_size(_, {integer,_,_}, _Bs) ->
+match_check_size(_, {integer,_,_}, _Bs, _AllowAll) ->
ok;
-match_check_size(_, {value,_,_}, _Bs) ->
+match_check_size(_, {value,_,_}, _Bs, _AllowAll) ->
ok; %From the debugger.
-match_check_size(_, _, _Bs) ->
+match_check_size(_, _, _Bs, _AllowAll) ->
throw(invalid).
%% error(Reason) -> exception thrown
diff --git a/lib/stdlib/src/file_sorter.erl b/lib/stdlib/src/file_sorter.erl
index 2bf88959b7..687d72b4bd 100644
--- a/lib/stdlib/src/file_sorter.erl
+++ b/lib/stdlib/src/file_sorter.erl
@@ -547,7 +547,7 @@ files(_I, L, _LSz, #w{seq = 1, out = Out}=W, []) ->
NW = close_input(W1),
outfun(close, NW);
Out ->
- write_run(L, W, Out),
+ _ = write_run(L, W, Out),
ok
end;
files(_I, L, _LSz, W, []) ->
@@ -638,7 +638,7 @@ last_merge(R, W) when length(R) =< W#w.no_files ->
NW = close_input(W2),
outfun(close, NW);
Out ->
- merge_files(R, W, Out),
+ _ = merge_files(R, W, Out),
ok
end;
last_merge(R, W) ->
@@ -1110,10 +1110,12 @@ read_fun2(Fd, Bin, Size, FileName, Owner) ->
end.
close_read_fun(Fd, _FileName, user) ->
- file:close(Fd);
+ _ = file:close(Fd),
+ ok;
close_read_fun(Fd, FileName, fsort) ->
- file:close(Fd),
- file:delete(FileName).
+ _ = file:close(Fd),
+ _ = file:delete(FileName),
+ ok.
read_objs(Fd, FileName, I, L, Bin0, Size0, LSz, W) ->
Max = erlang:max(Size0, ?CHUNKSIZE),
@@ -1481,10 +1483,10 @@ cleanup(W) ->
F = fun(IFun) when is_function(IFun) ->
IFun(close);
({Fd,FileName}) ->
- file:close(Fd),
- file:delete(FileName);
+ _ = file:close(Fd),
+ _= file:delete(FileName);
(FileName) ->
- file:delete(FileName)
+ _= file:delete(FileName)
end,
lists:foreach(F, W1#w.temp).
@@ -1502,8 +1504,12 @@ close_out(_) ->
close_file(Fd, W) ->
{Fd, FileName} = lists:keyfind(Fd, 1, W#w.temp),
?DEBUG("closing ~tp~n", [FileName]),
- file:close(Fd),
- W#w{temp = [FileName | lists:keydelete(Fd, 1, W#w.temp)]}.
+ case file:close(Fd) of
+ ok ->
+ W#w{temp = [FileName | lists:keydelete(Fd, 1, W#w.temp)]};
+ Error ->
+ file_error(FileName, Error, W)
+ end.
%%%
%%% Format 'term'.
@@ -1536,10 +1542,10 @@ file_rterms2(Fd, L, LSz, FileName, Files) when LSz < ?CHUNKSIZE ->
B = term_to_binary(Term),
file_rterms2(Fd, [B | L], LSz + byte_size(B), FileName, Files);
eof ->
- file:close(Fd),
+ _ = file:close(Fd),
{lists:reverse(L), file_rterms(no_file, Files)};
_Error ->
- file:close(Fd),
+ _ = file:close(Fd),
{error, {bad_term, FileName}}
end;
file_rterms2(Fd, L, _LSz, FileName, Files) ->
@@ -1568,7 +1574,7 @@ write_terms(Fd, F, [B | Bs], Args) ->
ok ->
write_terms(Fd, F, Bs, Args);
{error, Reason} ->
- file:close(Fd),
+ _ = file:close(Fd),
{error, {file_error, F, Reason}}
end;
write_terms(Fd, F, [], Args) ->
diff --git a/lib/stdlib/src/filelib.erl b/lib/stdlib/src/filelib.erl
index b8c0576e56..daae1fd2d2 100644
--- a/lib/stdlib/src/filelib.erl
+++ b/lib/stdlib/src/filelib.erl
@@ -234,7 +234,7 @@ ensure_dir(F) ->
%% Protect against infinite loop
{error,einval};
false ->
- ensure_dir(Dir),
+ _ = ensure_dir(Dir),
case file:make_dir(Dir) of
{error,eexist}=EExist ->
case do_is_dir(Dir, file) of
@@ -265,7 +265,7 @@ do_wildcard(Pattern, Cwd, Mod) ->
lists:sort(Files).
do_wildcard_1({exists,File}, Mod) ->
- case eval_read_file_info(File, Mod) of
+ case eval_read_link_info(File, Mod) of
{ok,_} -> [File];
_ -> []
end;
@@ -371,7 +371,7 @@ compile_wildcard(Pattern, Cwd0) ->
[Root|Rest] = filename:split(Pattern),
case filename:pathtype(Root) of
relative ->
- Cwd = filename:join([Cwd0]),
+ Cwd = prepare_base(Cwd0),
compile_wildcard_2([Root|Rest], {cwd,Cwd});
_ ->
compile_wildcard_2(Rest, {root,0,Root})
@@ -497,6 +497,16 @@ eval_read_file_info(File, erl_prim_loader) ->
eval_read_file_info(File, Mod) ->
Mod:read_file_info(File).
+eval_read_link_info(File, file) ->
+ file:read_link_info(File);
+eval_read_link_info(File, erl_prim_loader) ->
+ case erl_prim_loader:read_link_info(File) of
+ error -> {error, erl_prim_loader};
+ Res-> Res
+ end;
+eval_read_link_info(File, Mod) ->
+ Mod:read_link_info(File).
+
eval_list_dir(Dir, file) ->
file:list_dir(Dir);
eval_list_dir(Dir, erl_prim_loader) ->
diff --git a/lib/stdlib/src/filename.erl b/lib/stdlib/src/filename.erl
index 66e54ef221..e6bde5673c 100644
--- a/lib/stdlib/src/filename.erl
+++ b/lib/stdlib/src/filename.erl
@@ -516,8 +516,10 @@ pathtype(Atom) when is_atom(Atom) ->
pathtype(atom_to_list(Atom));
pathtype(Name) when is_list(Name) or is_binary(Name) ->
case os:type() of
- {unix, _} -> unix_pathtype(Name);
- {win32, _} -> win32_pathtype(Name)
+ {win32, _} ->
+ win32_pathtype(Name);
+ {_, _} ->
+ unix_pathtype(Name)
end.
unix_pathtype(<<$/,_/binary>>) ->
diff --git a/lib/stdlib/src/gb_sets.erl b/lib/stdlib/src/gb_sets.erl
index ba35a7170a..0a26d0182d 100644
--- a/lib/stdlib/src/gb_sets.erl
+++ b/lib/stdlib/src/gb_sets.erl
@@ -1,8 +1,7 @@
-%% -*- coding: utf-8 -*-
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2001-2012. All Rights Reserved.
+%% Copyright Ericsson AB 2001-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -197,31 +196,32 @@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% Some types.
--export_type([iter/0]).
+-export_type([set/0, set/1, iter/0, iter/1]).
--type gb_set_node() :: 'nil' | {term(), _, _}.
+-type gb_set_node(Element) :: 'nil' | {Element, _, _}.
+-type gb_set_node() :: gb_set_node(_).
+-opaque set(Element) :: {non_neg_integer(), gb_set_node(Element)}.
+-opaque set() :: set(_).
+-opaque iter(Element) :: [gb_set_node(Element)].
-opaque iter() :: [gb_set_node()].
-%% A declaration equivalent to the following is currently hard-coded
-%% in erl_types.erl
-%%
-%% -opaque gb_set() :: {non_neg_integer(), gb_set_node()}.
-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%%% gb_sets:set() in OTP 17 only.
+
-spec empty() -> Set when
- Set :: gb_set().
+ Set :: gb_sets:set().
empty() ->
{0, nil}.
-spec new() -> Set when
- Set :: gb_set().
+ Set :: gb_sets:set().
new() -> empty().
-spec is_empty(Set) -> boolean() when
- Set :: gb_set().
+ Set :: gb_sets:set().
is_empty({0, nil}) ->
true;
@@ -229,27 +229,24 @@ is_empty(_) ->
false.
-spec size(Set) -> non_neg_integer() when
- Set :: gb_set().
+ Set :: gb_sets:set().
size({Size, _}) ->
Size.
--spec singleton(Element) -> gb_set() when
- Element :: term().
+-spec singleton(Element) -> set(Element).
singleton(Key) ->
{1, {Key, nil, nil}}.
-spec is_element(Element, Set) -> boolean() when
- Element :: term(),
- Set :: gb_set().
+ Set :: set(Element).
is_element(Key, S) ->
is_member(Key, S).
-spec is_member(Element, Set) -> boolean() when
- Element :: term(),
- Set :: gb_set().
+ Set :: set(Element).
is_member(Key, {_, T}) ->
is_member_1(Key, T).
@@ -264,9 +261,8 @@ is_member_1(_, nil) ->
false.
-spec insert(Element, Set1) -> Set2 when
- Element :: term(),
- Set1 :: gb_set(),
- Set2 :: gb_set().
+ Set1 :: set(Element),
+ Set2 :: set(Element).
insert(Key, {S, T}) ->
S1 = S + 1,
@@ -323,8 +319,8 @@ count(nil) ->
{1, 0}.
-spec balance(Set1) -> Set2 when
- Set1 :: gb_set(),
- Set2 :: gb_set().
+ Set1 :: set(Element),
+ Set2 :: set(Element).
balance({S, T}) ->
{S, balance(T, S)}.
@@ -350,17 +346,15 @@ balance_list_1(L, 0) ->
{nil, L}.
-spec add_element(Element, Set1) -> Set2 when
- Element :: term(),
- Set1 :: gb_set(),
- Set2 :: gb_set().
+ Set1 :: set(Element),
+ Set2 :: set(Element).
add_element(X, S) ->
add(X, S).
-spec add(Element, Set1) -> Set2 when
- Element :: term(),
- Set1 :: gb_set(),
- Set2 :: gb_set().
+ Set1 :: set(Element),
+ Set2 :: set(Element).
add(X, S) ->
case is_member(X, S) of
@@ -371,32 +365,30 @@ add(X, S) ->
end.
-spec from_list(List) -> Set when
- List :: [term()],
- Set :: gb_set().
+ List :: [Element],
+ Set :: set(Element).
from_list(L) ->
from_ordset(ordsets:from_list(L)).
-spec from_ordset(List) -> Set when
- List :: [term()],
- Set :: gb_set().
+ List :: [Element],
+ Set :: set(Element).
from_ordset(L) ->
S = length(L),
{S, balance_list(L, S)}.
-spec del_element(Element, Set1) -> Set2 when
- Element :: term(),
- Set1 :: gb_set(),
- Set2 :: gb_set().
+ Set1 :: set(Element),
+ Set2 :: set(Element).
del_element(Key, S) ->
delete_any(Key, S).
-spec delete_any(Element, Set1) -> Set2 when
- Element :: term(),
- Set1 :: gb_set(),
- Set2 :: gb_set().
+ Set1 :: set(Element),
+ Set2 :: set(Element).
delete_any(Key, S) ->
case is_member(Key, S) of
@@ -407,9 +399,8 @@ delete_any(Key, S) ->
end.
-spec delete(Element, Set1) -> Set2 when
- Element :: term(),
- Set1 :: gb_set(),
- Set2 :: gb_set().
+ Set1 :: set(Element),
+ Set2 :: set(Element).
delete(Key, {S, T}) ->
{S - 1, delete_1(Key, T)}.
@@ -432,9 +423,8 @@ merge(Smaller, Larger) ->
{Key, Smaller, Larger1}.
-spec take_smallest(Set1) -> {Element, Set2} when
- Set1 :: gb_set(),
- Set2 :: gb_set(),
- Element :: term().
+ Set1 :: set(Element),
+ Set2 :: set(Element).
take_smallest({S, T}) ->
{Key, Larger} = take_smallest1(T),
@@ -446,8 +436,8 @@ take_smallest1({Key, Smaller, Larger}) ->
{Key1, Smaller1} = take_smallest1(Smaller),
{Key1, {Key, Smaller1, Larger}}.
--spec smallest(Set) -> term() when
- Set :: gb_set().
+-spec smallest(Set) -> Element when
+ Set :: set(Element).
smallest({_, T}) ->
smallest_1(T).
@@ -458,9 +448,8 @@ smallest_1({_Key, Smaller, _Larger}) ->
smallest_1(Smaller).
-spec take_largest(Set1) -> {Element, Set2} when
- Set1 :: gb_set(),
- Set2 :: gb_set(),
- Element :: term().
+ Set1 :: set(Element),
+ Set2 :: set(Element).
take_largest({S, T}) ->
{Key, Smaller} = take_largest1(T),
@@ -472,8 +461,8 @@ take_largest1({Key, Smaller, Larger}) ->
{Key1, Larger1} = take_largest1(Larger),
{Key1, {Key, Smaller, Larger1}}.
--spec largest(Set) -> term() when
- Set :: gb_set().
+-spec largest(Set) -> Element when
+ Set :: set(Element).
largest({_, T}) ->
largest_1(T).
@@ -484,8 +473,8 @@ largest_1({_Key, _Smaller, Larger}) ->
largest_1(Larger).
-spec to_list(Set) -> List when
- Set :: gb_set(),
- List :: [term()].
+ Set :: set(Element),
+ List :: [Element].
to_list({_, T}) ->
to_list(T, []).
@@ -497,8 +486,8 @@ to_list({Key, Small, Big}, L) ->
to_list(nil, L) -> L.
-spec iterator(Set) -> Iter when
- Set :: gb_set(),
- Iter :: iter().
+ Set :: set(Element),
+ Iter :: iter(Element).
iterator({_, T}) ->
iterator(T, []).
@@ -514,9 +503,8 @@ iterator(nil, As) ->
As.
-spec next(Iter1) -> {Element, Iter2} | 'none' when
- Iter1 :: iter(),
- Iter2 :: iter(),
- Element :: term().
+ Iter1 :: iter(Element),
+ Iter2 :: iter(Element).
next([{X, _, T} | As]) ->
{X, iterator(T, As)};
@@ -547,9 +535,9 @@ next([]) ->
%% overhead.
-spec union(Set1, Set2) -> Set3 when
- Set1 :: gb_set(),
- Set2 :: gb_set(),
- Set3 :: gb_set().
+ Set1 :: set(Element),
+ Set2 :: set(Element),
+ Set3 :: set(Element).
union({N1, T1}, {N2, T2}) when N2 < N1 ->
union(to_list_1(T2), N2, T1, N1);
@@ -571,7 +559,7 @@ union(L, N1, T2, N2) ->
union_1(L, mk_set(N2, T2))
end.
--spec mk_set(non_neg_integer(), gb_set_node()) -> gb_set().
+-spec mk_set(non_neg_integer(), gb_set_node(T)) -> set(T).
mk_set(N, T) ->
{N, T}.
@@ -652,8 +640,8 @@ balance_revlist_1(L, 0) ->
{nil, L}.
-spec union(SetList) -> Set when
- SetList :: [gb_set(),...],
- Set :: gb_set().
+ SetList :: [set(Element),...],
+ Set :: set(Element).
union([S | Ss]) ->
union_list(S, Ss);
@@ -667,9 +655,9 @@ union_list(S, []) -> S.
%% The rest is modelled on the above.
-spec intersection(Set1, Set2) -> Set3 when
- Set1 :: gb_set(),
- Set2 :: gb_set(),
- Set3 :: gb_set().
+ Set1 :: set(Element),
+ Set2 :: set(Element),
+ Set3 :: set(Element).
intersection({N1, T1}, {N2, T2}) when N2 < N1 ->
intersection(to_list_1(T2), N2, T1, N1);
@@ -718,8 +706,8 @@ intersection_2(_, [], As, S) ->
{S, balance_revlist(As, S)}.
-spec intersection(SetList) -> Set when
- SetList :: [gb_set(),...],
- Set :: gb_set().
+ SetList :: [set(Element),...],
+ Set :: set(Element).
intersection([S | Ss]) ->
intersection_list(S, Ss).
@@ -729,8 +717,8 @@ intersection_list(S, [S1 | Ss]) ->
intersection_list(S, []) -> S.
-spec is_disjoint(Set1, Set2) -> boolean() when
- Set1 :: gb_set(),
- Set2 :: gb_set().
+ Set1 :: set(Element),
+ Set2 :: set(Element).
is_disjoint({N1, T1}, {N2, T2}) when N1 < N2 ->
is_disjoint_1(T1, T2);
@@ -759,17 +747,17 @@ is_disjoint_1(_, nil) ->
%% traverse the whole element list of the left operand.
-spec subtract(Set1, Set2) -> Set3 when
- Set1 :: gb_set(),
- Set2 :: gb_set(),
- Set3 :: gb_set().
+ Set1 :: set(Element),
+ Set2 :: set(Element),
+ Set3 :: set(Element).
subtract(S1, S2) ->
difference(S1, S2).
-spec difference(Set1, Set2) -> Set3 when
- Set1 :: gb_set(),
- Set2 :: gb_set(),
- Set3 :: gb_set().
+ Set1 :: set(Element),
+ Set2 :: set(Element),
+ Set3 :: set(Element).
difference({N1, T1}, {N2, T2}) ->
difference(to_list_1(T1), N1, T2, N2).
@@ -818,8 +806,8 @@ difference_2(Xs, [], As, S) ->
%% without the construction of a new set.
-spec is_subset(Set1, Set2) -> boolean() when
- Set1 :: gb_set(),
- Set2 :: gb_set().
+ Set1 :: set(Element),
+ Set2 :: set(Element).
is_subset({N1, T1}, {N2, T2}) ->
is_subset(to_list_1(T1), N1, T2, N2).
@@ -868,20 +856,20 @@ is_set({N, {_, _, _}}) when is_integer(N), N >= 0 -> true;
is_set(_) -> false.
-spec filter(Pred, Set1) -> Set2 when
- Pred :: fun((E :: term()) -> boolean()),
- Set1 :: gb_set(),
- Set2 :: gb_set().
+ Pred :: fun((Element) -> boolean()),
+ Set1 :: set(Element),
+ Set2 :: set(Element).
filter(F, S) ->
from_ordset([X || X <- to_list(S), F(X)]).
-spec fold(Function, Acc0, Set) -> Acc1 when
- Function :: fun((E :: term(), AccIn) -> AccOut),
- Acc0 :: term(),
- Acc1 :: term(),
- AccIn :: term(),
- AccOut :: term(),
- Set :: gb_set().
+ Function :: fun((Element, AccIn) -> AccOut),
+ Acc0 :: Acc,
+ Acc1 :: Acc,
+ AccIn :: Acc,
+ AccOut :: Acc,
+ Set :: set(Element).
fold(F, A, {_, T}) when is_function(F, 2) ->
fold_1(F, A, T).
diff --git a/lib/stdlib/src/gb_trees.erl b/lib/stdlib/src/gb_trees.erl
index de0c239e26..7069b61873 100644
--- a/lib/stdlib/src/gb_trees.erl
+++ b/lib/stdlib/src/gb_trees.erl
@@ -1,8 +1,7 @@
-%% -*- coding: utf-8 -*-
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2001-2012. All Rights Reserved.
+%% Copyright Ericsson AB 2001-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -153,25 +152,25 @@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% Some types.
--export_type([iter/0]).
+-export_type([tree/0, tree/2, iter/0, iter/2]).
--type gb_tree_node() :: 'nil' | {_, _, _, _}.
+-type gb_tree_node(K, V) :: 'nil'
+ | {K, V, gb_tree_node(K, V), gb_tree_node(K, V)}.
+-type gb_tree_node() :: gb_tree_node(_, _).
+-opaque tree(Key, Value) :: {non_neg_integer(), gb_tree_node(Key, Value)}.
+-opaque tree() :: tree(_, _).
+-opaque iter(Key, Value) :: [gb_tree_node(Key, Value)].
-opaque iter() :: [gb_tree_node()].
-%% A declaration equivalent to the following is currently hard-coded
-%% in erl_types.erl
-%%
-%% -opaque gb_tree() :: {non_neg_integer(), gb_tree_node()}.
-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
--spec empty() -> gb_tree().
+-spec empty() -> tree().
empty() ->
{0, nil}.
-spec is_empty(Tree) -> boolean() when
- Tree :: gb_tree().
+ Tree :: tree().
is_empty({0, nil}) ->
true;
@@ -179,17 +178,15 @@ is_empty(_) ->
false.
-spec size(Tree) -> non_neg_integer() when
- Tree :: gb_tree().
+ Tree :: tree().
size({Size, _}) when is_integer(Size), Size >= 0 ->
Size.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
--spec lookup(Key, Tree) -> 'none' | {'value', Val} when
- Key :: term(),
- Val :: term(),
- Tree :: gb_tree().
+-spec lookup(Key, Tree) -> 'none' | {'value', Value} when
+ Tree :: tree(Key, Value).
lookup(Key, {_, T}) ->
lookup_1(Key, T).
@@ -215,8 +212,7 @@ lookup_1(_, nil) ->
%% This is a specialized version of `lookup'.
-spec is_defined(Key, Tree) -> boolean() when
- Key :: term(),
- Tree :: gb_tree().
+ Tree :: tree(Key, Value :: term()).
is_defined(Key, {_, T}) ->
is_defined_1(Key, T).
@@ -234,10 +230,8 @@ is_defined_1(_, nil) ->
%% This is a specialized version of `lookup'.
--spec get(Key, Tree) -> Val when
- Key :: term(),
- Tree :: gb_tree(),
- Val :: term().
+-spec get(Key, Tree) -> Value when
+ Tree :: tree(Key, Value).
get(Key, {_, T}) ->
get_1(Key, T).
@@ -251,11 +245,9 @@ get_1(_, {_, Value, _, _}) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
--spec update(Key, Val, Tree1) -> Tree2 when
- Key :: term(),
- Val :: term(),
- Tree1 :: gb_tree(),
- Tree2 :: gb_tree().
+-spec update(Key, Value, Tree1) -> Tree2 when
+ Tree1 :: tree(Key, Value),
+ Tree2 :: tree(Key, Value).
update(Key, Val, {S, T}) ->
T1 = update_1(Key, Val, T),
@@ -272,11 +264,9 @@ update_1(Key, Value, {_, _, Smaller, Bigger}) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
--spec insert(Key, Val, Tree1) -> Tree2 when
- Key :: term(),
- Val :: term(),
- Tree1 :: gb_tree(),
- Tree2 :: gb_tree().
+-spec insert(Key, Value, Tree1) -> Tree2 when
+ Tree1 :: tree(Key, Value),
+ Tree2 :: tree(Key, Value).
insert(Key, Val, {S, T}) when is_integer(S) ->
S1 = S+1,
@@ -325,11 +315,9 @@ insert_1(Key, _, _, _) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
--spec enter(Key, Val, Tree1) -> Tree2 when
- Key :: term(),
- Val :: term(),
- Tree1 :: gb_tree(),
- Tree2 :: gb_tree().
+-spec enter(Key, Value, Tree1) -> Tree2 when
+ Tree1 :: tree(Key, Value),
+ Tree2 :: tree(Key, Value).
enter(Key, Val, T) ->
case is_defined(Key, T) of
@@ -353,8 +341,8 @@ count(nil) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-spec balance(Tree1) -> Tree2 when
- Tree1 :: gb_tree(),
- Tree2 :: gb_tree().
+ Tree1 :: tree(Key, Value),
+ Tree2 :: tree(Key, Value).
balance({S, T}) ->
{S, balance(T, S)}.
@@ -380,8 +368,8 @@ balance_list_1(L, 0) ->
{nil, L}.
-spec from_orddict(List) -> Tree when
- List :: [{Key :: term(), Val :: term()}],
- Tree :: gb_tree().
+ List :: [{Key, Value}],
+ Tree :: tree(Key, Value).
from_orddict(L) ->
S = length(L),
@@ -390,9 +378,8 @@ from_orddict(L) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-spec delete_any(Key, Tree1) -> Tree2 when
- Key :: term(),
- Tree1 :: gb_tree(),
- Tree2 :: gb_tree().
+ Tree1 :: tree(Key, Value),
+ Tree2 :: tree(Key, Value).
delete_any(Key, T) ->
case is_defined(Key, T) of
@@ -405,9 +392,8 @@ delete_any(Key, T) ->
%%% delete. Assumes that key is present.
-spec delete(Key, Tree1) -> Tree2 when
- Key :: term(),
- Tree1 :: gb_tree(),
- Tree2 :: gb_tree().
+ Tree1 :: tree(Key, Value),
+ Tree2 :: tree(Key, Value).
delete(Key, {S, T}) when is_integer(S), S >= 0 ->
{S - 1, delete_1(Key, T)}.
@@ -433,11 +419,9 @@ merge(Smaller, Larger) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
--spec take_smallest(Tree1) -> {Key, Val, Tree2} when
- Tree1 :: gb_tree(),
- Tree2 :: gb_tree(),
- Key :: term(),
- Val :: term().
+-spec take_smallest(Tree1) -> {Key, Value, Tree2} when
+ Tree1 :: tree(Key, Value),
+ Tree2 :: tree(Key, Value).
take_smallest({Size, Tree}) when is_integer(Size), Size >= 0 ->
{Key, Value, Larger} = take_smallest1(Tree),
@@ -449,10 +433,8 @@ take_smallest1({Key, Value, Smaller, Larger}) ->
{Key1, Value1, Smaller1} = take_smallest1(Smaller),
{Key1, Value1, {Key, Value, Smaller1, Larger}}.
--spec smallest(Tree) -> {Key, Val} when
- Tree :: gb_tree(),
- Key :: term(),
- Val :: term().
+-spec smallest(Tree) -> {Key, Value} when
+ Tree :: tree(Key, Value).
smallest({_, Tree}) ->
smallest_1(Tree).
@@ -462,11 +444,9 @@ smallest_1({Key, Value, nil, _Larger}) ->
smallest_1({_Key, _Value, Smaller, _Larger}) ->
smallest_1(Smaller).
--spec take_largest(Tree1) -> {Key, Val, Tree2} when
- Tree1 :: gb_tree(),
- Tree2 :: gb_tree(),
- Key :: term(),
- Val :: term().
+-spec take_largest(Tree1) -> {Key, Value, Tree2} when
+ Tree1 :: tree(Key, Value),
+ Tree2 :: tree(Key, Value).
take_largest({Size, Tree}) when is_integer(Size), Size >= 0 ->
{Key, Value, Smaller} = take_largest1(Tree),
@@ -478,10 +458,8 @@ take_largest1({Key, Value, Smaller, Larger}) ->
{Key1, Value1, Larger1} = take_largest1(Larger),
{Key1, Value1, {Key, Value, Smaller, Larger1}}.
--spec largest(Tree) -> {Key, Val} when
- Tree :: gb_tree(),
- Key :: term(),
- Val :: term().
+-spec largest(Tree) -> {Key, Value} when
+ Tree :: tree(Key, Value).
largest({_, Tree}) ->
largest_1(Tree).
@@ -493,10 +471,8 @@ largest_1({_Key, _Value, _Smaller, Larger}) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
--spec to_list(Tree) -> [{Key, Val}] when
- Tree :: gb_tree(),
- Key :: term(),
- Val :: term().
+-spec to_list(Tree) -> [{Key, Value}] when
+ Tree :: tree(Key, Value).
to_list({_, T}) ->
to_list(T, []).
@@ -510,8 +486,7 @@ to_list(nil, L) -> L.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-spec keys(Tree) -> [Key] when
- Tree :: gb_tree(),
- Key :: term().
+ Tree :: tree(Key, Value :: term()).
keys({_, T}) ->
keys(T, []).
@@ -522,9 +497,8 @@ keys(nil, L) -> L.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
--spec values(Tree) -> [Val] when
- Tree :: gb_tree(),
- Val :: term().
+-spec values(Tree) -> [Value] when
+ Tree :: tree(Key :: term(), Value).
values({_, T}) ->
values(T, []).
@@ -536,8 +510,8 @@ values(nil, L) -> L.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-spec iterator(Tree) -> Iter when
- Tree :: gb_tree(),
- Iter :: iter().
+ Tree :: tree(Key, Value),
+ Iter :: iter(Key, Value).
iterator({_, T}) ->
iterator_1(T).
@@ -555,11 +529,9 @@ iterator({_, _, L, _} = T, As) ->
iterator(nil, As) ->
As.
--spec next(Iter1) -> 'none' | {Key, Val, Iter2} when
- Iter1 :: iter(),
- Iter2 :: iter(),
- Key :: term(),
- Val :: term().
+-spec next(Iter1) -> 'none' | {Key, Value, Iter2} when
+ Iter1 :: iter(Key, Value),
+ Iter2 :: iter(Key, Value).
next([{X, V, _, T} | As]) ->
{X, V, iterator(T, As)};
@@ -569,9 +541,9 @@ next([]) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-spec map(Function, Tree1) -> Tree2 when
- Function :: fun((K :: term(), V1 :: term()) -> V2 :: term()),
- Tree1 :: gb_tree(),
- Tree2 :: gb_tree().
+ Function :: fun((K :: Key, V1 :: Value1) -> V2 :: Value2),
+ Tree1 :: tree(Key, Value1),
+ Tree2 :: tree(Key, Value2).
map(F, {Size, Tree}) when is_function(F, 2) ->
{Size, map_1(F, Tree)}.
diff --git a/lib/stdlib/src/gen.erl b/lib/stdlib/src/gen.erl
index 7281549ea7..63116fa16e 100644
--- a/lib/stdlib/src/gen.erl
+++ b/lib/stdlib/src/gen.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -37,7 +37,9 @@
%%-----------------------------------------------------------------
-type linkage() :: 'link' | 'nolink'.
--type emgr_name() :: {'local', atom()} | {'global', term()} | {via, atom(), term()}.
+-type emgr_name() :: {'local', atom()}
+ | {'global', term()}
+ | {'via', Module :: module(), Name :: term()}.
-type start_ret() :: {'ok', pid()} | 'ignore' | {'error', term()}.
diff --git a/lib/stdlib/src/gen_event.erl b/lib/stdlib/src/gen_event.erl
index 7629e88fbf..469acdc37c 100644
--- a/lib/stdlib/src/gen_event.erl
+++ b/lib/stdlib/src/gen_event.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -40,6 +40,8 @@
system_continue/3,
system_terminate/4,
system_code_change/4,
+ system_get_state/1,
+ system_replace_state/2,
format_status/2]).
-export_type([handler/0, handler_args/0, add_handler_ret/0,
@@ -47,8 +49,6 @@
-import(error_logger, [error_msg/2]).
--define(reply(X), From ! {element(2,Tag), X}).
-
-record(handler, {module :: atom(),
id = false,
state,
@@ -229,24 +229,6 @@ wake_hib(Parent, ServerName, MSL, Debug) ->
fetch_msg(Parent, ServerName, MSL, Debug, Hib) ->
receive
- {system, From, get_state} ->
- States = [{Mod,Id,State} || #handler{module=Mod, id=Id, state=State} <- MSL],
- sys:handle_system_msg(get_state, From, Parent, ?MODULE, Debug,
- {States, [ServerName, MSL, Hib]}, Hib);
- {system, From, {replace_state, StateFun}} ->
- {NMSL, NStates} =
- lists:unzip([begin
- Cur = {Mod,Id,State},
- try
- NState = {Mod,Id,NS} = StateFun(Cur),
- {HS#handler{state=NS}, NState}
- catch
- _:_ ->
- {HS, Cur}
- end
- end || #handler{module=Mod, id=Id, state=State}=HS <- MSL]),
- sys:handle_system_msg(replace_state, From, Parent, ?MODULE, Debug,
- {NStates, [ServerName, NMSL, Hib]}, Hib);
{system, From, Req} ->
sys:handle_system_msg(Req, From, Parent, ?MODULE, Debug,
[ServerName, MSL, Hib],Hib);
@@ -265,49 +247,49 @@ handle_msg(Msg, Parent, ServerName, MSL, Debug) ->
{notify, Event} ->
{Hib,MSL1} = server_notify(Event, handle_event, MSL, ServerName),
loop(Parent, ServerName, MSL1, Debug, Hib);
- {From, Tag, {sync_notify, Event}} ->
+ {_From, Tag, {sync_notify, Event}} ->
{Hib, MSL1} = server_notify(Event, handle_event, MSL, ServerName),
- ?reply(ok),
+ reply(Tag, ok),
loop(Parent, ServerName, MSL1, Debug, Hib);
{'EXIT', From, Reason} ->
MSL1 = handle_exit(From, Reason, MSL, ServerName),
loop(Parent, ServerName, MSL1, Debug, false);
- {From, Tag, {call, Handler, Query}} ->
+ {_From, Tag, {call, Handler, Query}} ->
{Hib, Reply, MSL1} = server_call(Handler, Query, MSL, ServerName),
- ?reply(Reply),
+ reply(Tag, Reply),
loop(Parent, ServerName, MSL1, Debug, Hib);
- {From, Tag, {add_handler, Handler, Args}} ->
+ {_From, Tag, {add_handler, Handler, Args}} ->
{Hib, Reply, MSL1} = server_add_handler(Handler, Args, MSL),
- ?reply(Reply),
+ reply(Tag, Reply),
loop(Parent, ServerName, MSL1, Debug, Hib);
- {From, Tag, {add_sup_handler, Handler, Args, SupP}} ->
+ {_From, Tag, {add_sup_handler, Handler, Args, SupP}} ->
{Hib, Reply, MSL1} = server_add_sup_handler(Handler, Args, MSL, SupP),
- ?reply(Reply),
+ reply(Tag, Reply),
loop(Parent, ServerName, MSL1, Debug, Hib);
- {From, Tag, {delete_handler, Handler, Args}} ->
+ {_From, Tag, {delete_handler, Handler, Args}} ->
{Reply, MSL1} = server_delete_handler(Handler, Args, MSL,
ServerName),
- ?reply(Reply),
+ reply(Tag, Reply),
loop(Parent, ServerName, MSL1, Debug, false);
- {From, Tag, {swap_handler, Handler1, Args1, Handler2, Args2}} ->
+ {_From, Tag, {swap_handler, Handler1, Args1, Handler2, Args2}} ->
{Hib, Reply, MSL1} = server_swap_handler(Handler1, Args1, Handler2,
Args2, MSL, ServerName),
- ?reply(Reply),
+ reply(Tag, Reply),
loop(Parent, ServerName, MSL1, Debug, Hib);
- {From, Tag, {swap_sup_handler, Handler1, Args1, Handler2, Args2,
+ {_From, Tag, {swap_sup_handler, Handler1, Args1, Handler2, Args2,
Sup}} ->
{Hib, Reply, MSL1} = server_swap_handler(Handler1, Args1, Handler2,
Args2, MSL, Sup, ServerName),
- ?reply(Reply),
+ reply(Tag, Reply),
loop(Parent, ServerName, MSL1, Debug, Hib);
- {From, Tag, stop} ->
+ {_From, Tag, stop} ->
catch terminate_server(normal, Parent, MSL, ServerName),
- ?reply(ok);
- {From, Tag, which_handlers} ->
- ?reply(the_handlers(MSL)),
+ reply(Tag, ok);
+ {_From, Tag, which_handlers} ->
+ reply(Tag, the_handlers(MSL)),
loop(Parent, ServerName, MSL, Debug, false);
- {From, Tag, get_modules} ->
- ?reply(get_modules(MSL)),
+ {_From, Tag, get_modules} ->
+ reply(Tag, get_modules(MSL)),
loop(Parent, ServerName, MSL, Debug, false);
Other ->
{Hib, MSL1} = server_notify(Other, handle_info, MSL, ServerName),
@@ -319,6 +301,10 @@ terminate_server(Reason, Parent, MSL, ServerName) ->
do_unlink(Parent, MSL),
exit(Reason).
+reply({From, Ref}, Msg) ->
+ From ! {Ref, Msg},
+ ok.
+
%% unlink the supervisor process of all supervised handlers.
%% We do not want a handler supervisor to EXIT due to the
%% termination of the event manager (server).
@@ -383,6 +369,23 @@ system_code_change([ServerName, MSL, Hib], Module, OldVsn, Extra) ->
MSL),
{ok, [ServerName, MSL1, Hib]}.
+system_get_state([_ServerName, MSL, _Hib]) ->
+ {ok, [{Mod,Id,State} || #handler{module=Mod, id=Id, state=State} <- MSL]}.
+
+system_replace_state(StateFun, [ServerName, MSL, Hib]) ->
+ {NMSL, NStates} =
+ lists:unzip([begin
+ Cur = {Mod,Id,State},
+ try
+ NState = {Mod,Id,NS} = StateFun(Cur),
+ {HS#handler{state=NS}, NState}
+ catch
+ _:_ ->
+ {HS, Cur}
+ end
+ end || #handler{module=Mod, id=Id, state=State}=HS <- MSL]),
+ {ok, NStates, [ServerName, NMSL, Hib]}.
+
%%-----------------------------------------------------------------
%% Format debug messages. Print them as the call-back module sees
%% them, not as the real erlang messages. Use trace for that.
diff --git a/lib/stdlib/src/gen_fsm.erl b/lib/stdlib/src/gen_fsm.erl
index 9e9d4ee4bb..5afe3e8b09 100644
--- a/lib/stdlib/src/gen_fsm.erl
+++ b/lib/stdlib/src/gen_fsm.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -118,6 +118,8 @@
system_continue/3,
system_terminate/4,
system_code_change/4,
+ system_get_state/1,
+ system_replace_state/2,
format_status/2]).
-import(error_logger, [format/2]).
@@ -422,17 +424,6 @@ wake_hib(Parent, Name, StateName, StateData, Mod, Debug) ->
decode_msg(Msg,Parent, Name, StateName, StateData, Mod, Time, Debug, Hib) ->
case Msg of
- {system, From, get_state} ->
- Misc = [Name, StateName, StateData, Mod, Time],
- sys:handle_system_msg(get_state, From, Parent, ?MODULE, Debug,
- {{StateName, StateData}, Misc}, Hib);
- {system, From, {replace_state, StateFun}} ->
- State = {StateName, StateData},
- NState = {NStateName, NStateData} = try StateFun(State)
- catch _:_ -> State end,
- NMisc = [Name, NStateName, NStateData, Mod, Time],
- sys:handle_system_msg(replace_state, From, Parent, ?MODULE, Debug,
- {NState, NMisc}, Hib);
{system, From, Req} ->
sys:handle_system_msg(Req, From, Parent, ?MODULE, Debug,
[Name, StateName, StateData, Mod, Time], Hib);
@@ -467,6 +458,13 @@ system_code_change([Name, StateName, StateData, Mod, Time],
Else -> Else
end.
+system_get_state([_Name, StateName, StateData, _Mod, _Time]) ->
+ {ok, {StateName, StateData}}.
+
+system_replace_state(StateFun, [Name, StateName, StateData, Mod, Time]) ->
+ Result = {NStateName, NStateData} = StateFun({StateName, StateData}),
+ {ok, Result, [Name, NStateName, NStateData, Mod, Time]}.
+
%%-----------------------------------------------------------------
%% Format debug messages. Print them as the call-back module sees
%% them, not as the real erlang messages. Use trace for that.
@@ -549,7 +547,7 @@ handle_msg(Msg, Parent, Name, StateName, StateData, Mod, _Time, Debug) ->
{stop, Reason, Reply, NStateData} when From =/= undefined ->
{'EXIT', R} = (catch terminate(Reason, Name, Msg, Mod,
StateName, NStateData, Debug)),
- reply(Name, From, Reply, Debug, StateName),
+ _ = reply(Name, From, Reply, Debug, StateName),
exit(R);
{'EXIT', What} ->
terminate(What, Name, Msg, Mod, StateName, StateData, Debug);
@@ -596,7 +594,8 @@ reply(Name, {To, Tag}, Reply, Debug, StateName) ->
terminate(Reason, Name, Msg, Mod, StateName, StateData, Debug) ->
case catch Mod:terminate(Reason, StateName, StateData) of
{'EXIT', R} ->
- error_info(R, Name, Msg, StateName, StateData, Debug),
+ FmtStateData = format_status(terminate, Mod, get(), StateData),
+ error_info(R, Name, Msg, StateName, FmtStateData, Debug),
exit(R);
_ ->
case Reason of
@@ -607,17 +606,7 @@ terminate(Reason, Name, Msg, Mod, StateName, StateData, Debug) ->
{shutdown,_}=Shutdown ->
exit(Shutdown);
_ ->
- FmtStateData =
- case erlang:function_exported(Mod, format_status, 2) of
- true ->
- Args = [get(), StateData],
- case catch Mod:format_status(terminate, Args) of
- {'EXIT', _} -> StateData;
- Else -> Else
- end;
- _ ->
- StateData
- end,
+ FmtStateData = format_status(terminate, Mod, get(), StateData),
error_info(Reason,Name,Msg,StateName,FmtStateData,Debug),
exit(Reason)
end
@@ -682,21 +671,29 @@ format_status(Opt, StatusData) ->
Header = gen:format_status_header("Status for state machine",
Name),
Log = sys:get_debug(log, Debug, []),
- DefaultStatus = [{data, [{"StateData", StateData}]}],
- Specfic =
- case erlang:function_exported(Mod, format_status, 2) of
- true ->
- case catch Mod:format_status(Opt,[PDict,StateData]) of
- {'EXIT', _} -> DefaultStatus;
- StatusList when is_list(StatusList) -> StatusList;
- Else -> [Else]
- end;
- _ ->
- DefaultStatus
- end,
+ Specfic = format_status(Opt, Mod, PDict, StateData),
+ Specfic = case format_status(Opt, Mod, PDict, StateData) of
+ S when is_list(S) -> S;
+ S -> [S]
+ end,
[{header, Header},
{data, [{"Status", SysState},
{"Parent", Parent},
{"Logged events", Log},
{"StateName", StateName}]} |
Specfic].
+
+format_status(Opt, Mod, PDict, State) ->
+ DefStatus = case Opt of
+ terminate -> State;
+ _ -> [{data, [{"StateData", State}]}]
+ end,
+ case erlang:function_exported(Mod, format_status, 2) of
+ true ->
+ case catch Mod:format_status(Opt, [PDict, State]) of
+ {'EXIT', _} -> DefStatus;
+ Else -> Else
+ end;
+ _ ->
+ DefStatus
+ end.
diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl
index df68a37c06..18ef4a2507 100644
--- a/lib/stdlib/src/gen_server.erl
+++ b/lib/stdlib/src/gen_server.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -98,6 +98,8 @@
-export([system_continue/3,
system_terminate/4,
system_code_change/4,
+ system_get_state/1,
+ system_replace_state/2,
format_status/2]).
%% Internal exports
@@ -372,13 +374,6 @@ wake_hib(Parent, Name, State, Mod, Debug) ->
decode_msg(Msg, Parent, Name, State, Mod, Time, Debug, Hib) ->
case Msg of
- {system, From, get_state} ->
- sys:handle_system_msg(get_state, From, Parent, ?MODULE, Debug,
- {State, [Name, State, Mod, Time]}, Hib);
- {system, From, {replace_state, StateFun}} ->
- NState = try StateFun(State) catch _:_ -> State end,
- sys:handle_system_msg(replace_state, From, Parent, ?MODULE, Debug,
- {NState, [Name, NState, Mod, Time]}, Hib);
{system, From, Req} ->
sys:handle_system_msg(Req, From, Parent, ?MODULE, Debug,
[Name, State, Mod, Time], Hib);
@@ -572,28 +567,88 @@ start_monitor(Node, Name) when is_atom(Node), is_atom(Name) ->
end
end.
+%% ---------------------------------------------------
+%% Helper functions for try-catch of callbacks.
+%% Returns the return value of the callback, or
+%% {'EXIT', ExitReason, ReportReason} (if an exception occurs)
+%%
+%% ExitReason is the reason that shall be used when the process
+%% terminates.
+%%
+%% ReportReason is the reason that shall be printed in the error
+%% report.
+%%
+%% These functions are introduced in order to add the stack trace in
+%% the error report produced when a callback is terminated with
+%% erlang:exit/1 (OTP-12263).
+%% ---------------------------------------------------
+
+try_dispatch({'$gen_cast', Msg}, Mod, State) ->
+ try_dispatch(Mod, handle_cast, Msg, State);
+try_dispatch(Info, Mod, State) ->
+ try_dispatch(Mod, handle_info, Info, State).
+
+try_dispatch(Mod, Func, Msg, State) ->
+ try
+ {ok, Mod:Func(Msg, State)}
+ catch
+ throw:R ->
+ {ok, R};
+ error:R ->
+ Stacktrace = erlang:get_stacktrace(),
+ {'EXIT', {R, Stacktrace}, {R, Stacktrace}};
+ exit:R ->
+ Stacktrace = erlang:get_stacktrace(),
+ {'EXIT', R, {R, Stacktrace}}
+ end.
+
+try_handle_call(Mod, Msg, From, State) ->
+ try
+ {ok, Mod:handle_call(Msg, From, State)}
+ catch
+ throw:R ->
+ {ok, R};
+ error:R ->
+ Stacktrace = erlang:get_stacktrace(),
+ {'EXIT', {R, Stacktrace}, {R, Stacktrace}};
+ exit:R ->
+ Stacktrace = erlang:get_stacktrace(),
+ {'EXIT', R, {R, Stacktrace}}
+ end.
+
+try_terminate(Mod, Reason, State) ->
+ try
+ {ok, Mod:terminate(Reason, State)}
+ catch
+ throw:R ->
+ {ok, R};
+ error:R ->
+ Stacktrace = erlang:get_stacktrace(),
+ {'EXIT', {R, Stacktrace}, {R, Stacktrace}};
+ exit:R ->
+ Stacktrace = erlang:get_stacktrace(),
+ {'EXIT', R, {R, Stacktrace}}
+ end.
+
+
%%% ---------------------------------------------------
%%% Message handling functions
%%% ---------------------------------------------------
-dispatch({'$gen_cast', Msg}, Mod, State) ->
- Mod:handle_cast(Msg, State);
-dispatch(Info, Mod, State) ->
- Mod:handle_info(Info, State).
-
handle_msg({'$gen_call', From, Msg}, Parent, Name, State, Mod) ->
- case catch Mod:handle_call(Msg, From, State) of
- {reply, Reply, NState} ->
+ Result = try_handle_call(Mod, Msg, From, State),
+ case Result of
+ {ok, {reply, Reply, NState}} ->
reply(From, Reply),
loop(Parent, Name, NState, Mod, infinity, []);
- {reply, Reply, NState, Time1} ->
+ {ok, {reply, Reply, NState, Time1}} ->
reply(From, Reply),
loop(Parent, Name, NState, Mod, Time1, []);
- {noreply, NState} ->
+ {ok, {noreply, NState}} ->
loop(Parent, Name, NState, Mod, infinity, []);
- {noreply, NState, Time1} ->
+ {ok, {noreply, NState, Time1}} ->
loop(Parent, Name, NState, Mod, Time1, []);
- {stop, Reason, Reply, NState} ->
+ {ok, {stop, Reason, Reply, NState}} ->
{'EXIT', R} =
(catch terminate(Reason, Name, Msg, Mod, NState, [])),
reply(From, Reply),
@@ -601,67 +656,68 @@ handle_msg({'$gen_call', From, Msg}, Parent, Name, State, Mod) ->
Other -> handle_common_reply(Other, Parent, Name, Msg, Mod, State)
end;
handle_msg(Msg, Parent, Name, State, Mod) ->
- Reply = (catch dispatch(Msg, Mod, State)),
+ Reply = try_dispatch(Msg, Mod, State),
handle_common_reply(Reply, Parent, Name, Msg, Mod, State).
handle_msg({'$gen_call', From, Msg}, Parent, Name, State, Mod, Debug) ->
- case catch Mod:handle_call(Msg, From, State) of
- {reply, Reply, NState} ->
+ Result = try_handle_call(Mod, Msg, From, State),
+ case Result of
+ {ok, {reply, Reply, NState}} ->
Debug1 = reply(Name, From, Reply, NState, Debug),
loop(Parent, Name, NState, Mod, infinity, Debug1);
- {reply, Reply, NState, Time1} ->
+ {ok, {reply, Reply, NState, Time1}} ->
Debug1 = reply(Name, From, Reply, NState, Debug),
loop(Parent, Name, NState, Mod, Time1, Debug1);
- {noreply, NState} ->
+ {ok, {noreply, NState}} ->
Debug1 = sys:handle_debug(Debug, fun print_event/3, Name,
{noreply, NState}),
loop(Parent, Name, NState, Mod, infinity, Debug1);
- {noreply, NState, Time1} ->
+ {ok, {noreply, NState, Time1}} ->
Debug1 = sys:handle_debug(Debug, fun print_event/3, Name,
{noreply, NState}),
loop(Parent, Name, NState, Mod, Time1, Debug1);
- {stop, Reason, Reply, NState} ->
+ {ok, {stop, Reason, Reply, NState}} ->
{'EXIT', R} =
(catch terminate(Reason, Name, Msg, Mod, NState, Debug)),
- reply(Name, From, Reply, NState, Debug),
+ _ = reply(Name, From, Reply, NState, Debug),
exit(R);
Other ->
handle_common_reply(Other, Parent, Name, Msg, Mod, State, Debug)
end;
handle_msg(Msg, Parent, Name, State, Mod, Debug) ->
- Reply = (catch dispatch(Msg, Mod, State)),
+ Reply = try_dispatch(Msg, Mod, State),
handle_common_reply(Reply, Parent, Name, Msg, Mod, State, Debug).
handle_common_reply(Reply, Parent, Name, Msg, Mod, State) ->
case Reply of
- {noreply, NState} ->
+ {ok, {noreply, NState}} ->
loop(Parent, Name, NState, Mod, infinity, []);
- {noreply, NState, Time1} ->
+ {ok, {noreply, NState, Time1}} ->
loop(Parent, Name, NState, Mod, Time1, []);
- {stop, Reason, NState} ->
+ {ok, {stop, Reason, NState}} ->
terminate(Reason, Name, Msg, Mod, NState, []);
- {'EXIT', What} ->
- terminate(What, Name, Msg, Mod, State, []);
- _ ->
- terminate({bad_return_value, Reply}, Name, Msg, Mod, State, [])
+ {'EXIT', ExitReason, ReportReason} ->
+ terminate(ExitReason, ReportReason, Name, Msg, Mod, State, []);
+ {ok, BadReply} ->
+ terminate({bad_return_value, BadReply}, Name, Msg, Mod, State, [])
end.
handle_common_reply(Reply, Parent, Name, Msg, Mod, State, Debug) ->
case Reply of
- {noreply, NState} ->
+ {ok, {noreply, NState}} ->
Debug1 = sys:handle_debug(Debug, fun print_event/3, Name,
{noreply, NState}),
loop(Parent, Name, NState, Mod, infinity, Debug1);
- {noreply, NState, Time1} ->
+ {ok, {noreply, NState, Time1}} ->
Debug1 = sys:handle_debug(Debug, fun print_event/3, Name,
{noreply, NState}),
loop(Parent, Name, NState, Mod, Time1, Debug1);
- {stop, Reason, NState} ->
+ {ok, {stop, Reason, NState}} ->
terminate(Reason, Name, Msg, Mod, NState, Debug);
- {'EXIT', What} ->
- terminate(What, Name, Msg, Mod, State, Debug);
- _ ->
- terminate({bad_return_value, Reply}, Name, Msg, Mod, State, Debug)
+ {'EXIT', ExitReason, ReportReason} ->
+ terminate(ExitReason, ReportReason, Name, Msg, Mod, State, Debug);
+ {ok, BadReply} ->
+ terminate({bad_return_value, BadReply}, Name, Msg, Mod, State, Debug)
end.
reply(Name, {To, Tag}, Reply, State, Debug) ->
@@ -687,6 +743,13 @@ system_code_change([Name, State, Mod, Time], _Module, OldVsn, Extra) ->
Else -> Else
end.
+system_get_state([_Name, State, _Mod, _Time]) ->
+ {ok, State}.
+
+system_replace_state(StateFun, [Name, State, Mod, Time]) ->
+ NState = StateFun(State),
+ {ok, NState, [Name, NState, Mod, Time]}.
+
%%-----------------------------------------------------------------
%% Format debug messages. Print them as the call-back module sees
%% them, not as the real erlang messages. Use trace for that.
@@ -715,13 +778,20 @@ print_event(Dev, Event, Name) ->
%%% Terminate the server.
%%% ---------------------------------------------------
+-spec terminate(_, _, _, _, _, _) -> no_return().
terminate(Reason, Name, Msg, Mod, State, Debug) ->
- case catch Mod:terminate(Reason, State) of
- {'EXIT', R} ->
- error_info(R, Name, Msg, State, Debug),
- exit(R);
+ terminate(Reason, Reason, Name, Msg, Mod, State, Debug).
+
+-spec terminate(_, _, _, _, _, _, _) -> no_return().
+terminate(ExitReason, ReportReason, Name, Msg, Mod, State, Debug) ->
+ Reply = try_terminate(Mod, ExitReason, State),
+ case Reply of
+ {'EXIT', ExitReason1, ReportReason1} ->
+ FmtState = format_status(terminate, Mod, get(), State),
+ error_info(ReportReason1, Name, Msg, FmtState, Debug),
+ exit(ExitReason1);
_ ->
- case Reason of
+ case ExitReason of
normal ->
exit(normal);
shutdown ->
@@ -729,19 +799,9 @@ terminate(Reason, Name, Msg, Mod, State, Debug) ->
{shutdown,_}=Shutdown ->
exit(Shutdown);
_ ->
- FmtState =
- case erlang:function_exported(Mod, format_status, 2) of
- true ->
- Args = [get(), State],
- case catch Mod:format_status(terminate, Args) of
- {'EXIT', _} -> State;
- Else -> Else
- end;
- _ ->
- State
- end,
- error_info(Reason, Name, Msg, FmtState, Debug),
- exit(Reason)
+ FmtState = format_status(terminate, Mod, get(), State),
+ error_info(ReportReason, Name, Msg, FmtState, Debug),
+ exit(ExitReason)
end
end.
@@ -873,23 +933,29 @@ name_to_pid(Name) ->
%%-----------------------------------------------------------------
format_status(Opt, StatusData) ->
[PDict, SysState, Parent, Debug, [Name, State, Mod, _Time]] = StatusData,
- Header = gen:format_status_header("Status for generic server",
- Name),
+ Header = gen:format_status_header("Status for generic server", Name),
Log = sys:get_debug(log, Debug, []),
- DefaultStatus = [{data, [{"State", State}]}],
- Specfic =
- case erlang:function_exported(Mod, format_status, 2) of
- true ->
- case catch Mod:format_status(Opt, [PDict, State]) of
- {'EXIT', _} -> DefaultStatus;
- StatusList when is_list(StatusList) -> StatusList;
- Else -> [Else]
- end;
- _ ->
- DefaultStatus
- end,
+ Specfic = case format_status(Opt, Mod, PDict, State) of
+ S when is_list(S) -> S;
+ S -> [S]
+ end,
[{header, Header},
{data, [{"Status", SysState},
{"Parent", Parent},
{"Logged events", Log}]} |
Specfic].
+
+format_status(Opt, Mod, PDict, State) ->
+ DefStatus = case Opt of
+ terminate -> State;
+ _ -> [{data, [{"State", State}]}]
+ end,
+ case erlang:function_exported(Mod, format_status, 2) of
+ true ->
+ case catch Mod:format_status(Opt, [PDict, State]) of
+ {'EXIT', _} -> DefStatus;
+ Else -> Else
+ end;
+ _ ->
+ DefStatus
+ end.
diff --git a/lib/stdlib/src/io.erl b/lib/stdlib/src/io.erl
index b11d41e2eb..b9ace2f442 100644
--- a/lib/stdlib/src/io.erl
+++ b/lib/stdlib/src/io.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -177,13 +177,15 @@ get_password(Io) ->
| {'expand_fun', expand_fun()}
| {'encoding', encoding()}.
--spec getopts() -> [opt_pair()].
+-spec getopts() -> [opt_pair()] | {'error', Reason} when
+ Reason :: term().
getopts() ->
getopts(default_input()).
--spec getopts(IoDevice) -> [opt_pair()] when
- IoDevice :: device().
+-spec getopts(IoDevice) -> [opt_pair()] | {'error', Reason} when
+ IoDevice :: device(),
+ Reason :: term().
getopts(Io) ->
request(Io, getopts).
@@ -564,12 +566,23 @@ request(Name, Request) when is_atom(Name) ->
execute_request(Pid, {Convert,Converted}) ->
Mref = erlang:monitor(process, Pid),
- Pid ! {io_request,self(),Pid,Converted},
- if
- Convert ->
- convert_binaries(wait_io_mon_reply(Pid, Mref));
- true ->
- wait_io_mon_reply(Pid, Mref)
+ Pid ! {io_request,self(),Mref,Converted},
+
+ receive
+ {io_reply, Mref, Reply} ->
+ erlang:demonitor(Mref, [flush]),
+ if
+ Convert ->
+ convert_binaries(Reply);
+ true ->
+ Reply
+ end;
+ {'DOWN', Mref, _, _, _} ->
+ receive
+ {'EXIT', Pid, _What} -> true
+ after 0 -> true
+ end,
+ {error,terminated}
end.
requests(Requests) -> %Requests as atomic action
@@ -595,26 +608,6 @@ default_input() ->
default_output() ->
group_leader().
-wait_io_mon_reply(From, Mref) ->
- receive
- {io_reply, From, Reply} ->
- erlang:demonitor(Mref, [flush]),
- Reply;
- {'EXIT', From, _What} ->
- receive
- {'DOWN', Mref, _, _, _} -> true
- after 0 -> true
- end,
- {error,terminated};
- {'DOWN', Mref, _, _, _} ->
- receive
- {'EXIT', From, _What} -> true
- after 0 -> true
- end,
- {error,terminated}
- end.
-
-
%% io_requests(Requests)
%% Transform requests into correct i/o server messages. Only handle the
%% one we KNOW must be changed, others, including incorrect ones, are
diff --git a/lib/stdlib/src/io_lib.erl b/lib/stdlib/src/io_lib.erl
index 9e69601770..adc9a0cf5f 100644
--- a/lib/stdlib/src/io_lib.erl
+++ b/lib/stdlib/src/io_lib.erl
@@ -1,4 +1,3 @@
-%% -*- coding: utf-8 -*-
%%
%% %CopyrightBegin%
%%
@@ -258,7 +257,9 @@ write(T, D) when is_tuple(T) ->
[write(element(1, T), D-1)|
write_tail(tl(tuple_to_list(T)), D-1, $,)],
$}]
- end.
+ end;
+%write(Term, D) when is_map(Term) -> write_map(Term, D);
+write(Term, D) -> write_map(Term, D).
%% write_tail(List, Depth, CharacterBeforeDots)
%% Test the terminating case first as this looks better with depth.
@@ -276,6 +277,18 @@ write_port(Port) ->
write_ref(Ref) ->
erlang:ref_to_list(Ref).
+write_map(Map, D) when is_integer(D) ->
+ [$#,${,write_map_body(maps:to_list(Map), D),$}].
+
+write_map_body(_, 0) -> "...";
+write_map_body([],_) -> [];
+write_map_body([{K,V}],D) -> write_map_assoc(K,V,D);
+write_map_body([{K,V}|KVs], D) ->
+ [write_map_assoc(K,V,D),$, | write_map_body(KVs,D-1)].
+
+write_map_assoc(K,V,D) ->
+ [write(K,D - 1),"=>",write(V,D-1)].
+
write_binary(B, D) when is_integer(D) ->
[$<,$<,write_binary_body(B, D),$>,$>].
diff --git a/lib/stdlib/src/io_lib_format.erl b/lib/stdlib/src/io_lib_format.erl
index 56e15a17ec..89ae6fb187 100644
--- a/lib/stdlib/src/io_lib_format.erl
+++ b/lib/stdlib/src/io_lib_format.erl
@@ -255,7 +255,7 @@ term(T, none, _Adj, none, _Pad) -> T;
term(T, none, Adj, P, Pad) -> term(T, P, Adj, P, Pad);
term(T, F, Adj, P0, Pad) ->
L = lists:flatlength(T),
- P = case P0 of none -> erlang:min(L, F); _ -> P0 end,
+ P = erlang:min(L, case P0 of none -> F; _ -> min(P0, F) end),
if
L > P ->
adjust(chars($*, P), chars(Pad, F-P), Adj);
diff --git a/lib/stdlib/src/io_lib_pretty.erl b/lib/stdlib/src/io_lib_pretty.erl
index 7637ad7a3d..aece06afa6 100644
--- a/lib/stdlib/src/io_lib_pretty.erl
+++ b/lib/stdlib/src/io_lib_pretty.erl
@@ -64,13 +64,13 @@ print(Term) ->
(term(), options()) -> chars().
print(Term, Options) when is_list(Options) ->
- Col = proplists:get_value(column, Options, 1),
- Ll = proplists:get_value(line_length, Options, 80),
- D = proplists:get_value(depth, Options, -1),
- M = proplists:get_value(max_chars, Options, -1),
- RecDefFun = proplists:get_value(record_print_fun, Options, no_fun),
- Encoding = proplists:get_value(encoding, Options, epp:default_encoding()),
- Strings = proplists:get_value(strings, Options, true),
+ Col = get_option(column, Options, 1),
+ Ll = get_option(line_length, Options, 80),
+ D = get_option(depth, Options, -1),
+ M = get_option(max_chars, Options, -1),
+ RecDefFun = get_option(record_print_fun, Options, no_fun),
+ Encoding = get_option(encoding, Options, epp:default_encoding()),
+ Strings = get_option(strings, Options, true),
print(Term, Col, Ll, D, M, RecDefFun, Encoding, Strings);
print(Term, RecDefFun) ->
print(Term, -1, RecDefFun).
@@ -101,6 +101,7 @@ print(Term, Col, Ll, D, M, RecDefFun, Enc, Str) when Col =< 0 ->
print(Term, 1, Ll, D, M, RecDefFun, Enc, Str);
print(Term, Col, Ll, D, M0, RecDefFun, Enc, Str) when is_tuple(Term);
is_list(Term);
+ is_map(Term);
is_bitstring(Term) ->
If = {_S, Len} = print_length(Term, D, RecDefFun, Enc, Str),
M = max_cs(M0, Len),
@@ -137,6 +138,10 @@ pp({{tuple,true,L}, _Len}, Col, Ll, M, TInd, Ind, LD, W) ->
[${, pp_tag_tuple(L, Col, Ll, M, TInd, Ind, LD, W + 1), $}];
pp({{tuple,false,L}, _Len}, Col, Ll, M, TInd, Ind, LD, W) ->
[${, pp_list(L, Col + 1, Ll, M, TInd, indent(1, Ind), LD, $,, W + 1), $}];
+pp({{map,Pairs},_Len}, Col, Ll, M, TInd, Ind, LD, W) ->
+ [$#,${, pp_list(Pairs, Col + 2, Ll, M, TInd, indent(2, Ind), LD, $,, W + 1), $}];
+pp({{map_pair,K,V},_Len}, Col, Ll, M, TInd, Ind, LD, W) ->
+ [pp(K, Col, Ll, M, TInd, Ind, LD, W), " => ", pp(V, Col, Ll, M, TInd, Ind, LD, W)];
pp({{record,[{Name,NLen} | L]}, _Len}, Col, Ll, M, TInd, Ind, LD, W) ->
[Name, ${, pp_record(L, NLen, Col, Ll, M, TInd, Ind, LD, W + NLen+1), $}];
pp({{bin,S}, _Len}, Col, Ll, M, _TInd, Ind, LD, W) ->
@@ -283,6 +288,10 @@ write({{tuple, _IsTagged, L}, _}) ->
[${, write_list(L, $,), $}];
write({{list, L}, _}) ->
[$[, write_list(L, $|), $]];
+write({{map, Pairs}, _}) ->
+ [$#,${, write_list(Pairs, $,), $}];
+write({{map_pair, K, V}, _}) ->
+ [write(K)," => ",write(V)];
write({{record, [{Name,_} | L]}, _}) ->
[Name, ${, write_fields(L), $}];
write({{bin, S}, _}) ->
@@ -331,6 +340,8 @@ print_length([], _D, _RF, _Enc, _Str) ->
{"[]", 2};
print_length({}, _D, _RF, _Enc, _Str) ->
{"{}", 2};
+print_length(#{}=M, _D, _RF, _Enc, _Str) when map_size(M) =:= 0 ->
+ {"#{}", 3};
print_length(List, D, RF, Enc, Str) when is_list(List) ->
case Str andalso printable_list(List, D, Enc) of
true ->
@@ -356,6 +367,8 @@ print_length(R, D, RF, Enc, Str) when is_atom(element(1, R)),
end;
print_length(Tuple, D, RF, Enc, Str) when is_tuple(Tuple) ->
print_length_tuple(Tuple, D, RF, Enc, Str);
+print_length(Map, D, RF, Enc, Str) when is_map(Map) ->
+ print_length_map(Map, D, RF, Enc, Str);
print_length(<<>>, _D, _RF, _Enc, _Str) ->
{"<<>>", 4};
print_length(<<_/bitstring>>, 1, _RF, _Enc, _Str) ->
@@ -389,6 +402,25 @@ print_length(Term, _D, _RF, _Enc, _Str) ->
S = io_lib:write(Term),
{S, lists:flatlength(S)}.
+print_length_map(_Map, 1, _RF, _Enc, _Str) ->
+ {"#{...}", 6};
+print_length_map(Map, D, RF, Enc, Str) when is_map(Map) ->
+ Pairs = print_length_map_pairs(maps:to_list(Map), D, RF, Enc, Str),
+ {{map, Pairs}, list_length(Pairs, 3)}.
+
+print_length_map_pairs([], _D, _RF, _Enc, _Str) ->
+ [];
+print_length_map_pairs(_Pairs, 1, _RF, _Enc, _Str) ->
+ {dots, 3};
+print_length_map_pairs([{K,V}|Pairs], D, RF, Enc, Str) ->
+ [print_length_map_pair(K,V,D-1,RF,Enc,Str) |
+ print_length_map_pairs(Pairs,D-1,RF,Enc,Str)].
+
+print_length_map_pair(K, V, D, RF, Enc, Str) ->
+ {KS, KL} = print_length(K, D, RF, Enc, Str),
+ {VS, VL} = print_length(V, D, RF, Enc, Str),
+ {{map_pair, {KS,KL}, {VS,VL}}, KL + VL}.
+
print_length_tuple(_Tuple, 1, _RF, _Enc, _Str) ->
{"{...}", 5};
print_length_tuple(Tuple, D, RF, Enc, Str) ->
@@ -727,3 +759,10 @@ chars(C, N) when (N band 1) =:= 0 ->
chars(C, N) ->
S = chars(C, N bsr 1),
[C, S | S].
+
+get_option(Key, TupleList, Default) ->
+ case lists:keyfind(Key, 1, TupleList) of
+ false -> Default;
+ {Key, Value} -> Value;
+ _ -> Default
+ end.
diff --git a/lib/stdlib/src/lists.erl b/lib/stdlib/src/lists.erl
index d6a9f4645d..6303465d3d 100644
--- a/lib/stdlib/src/lists.erl
+++ b/lib/stdlib/src/lists.erl
@@ -22,7 +22,7 @@
-compile({no_auto_import,[min/2]}).
-export([append/2, append/1, subtract/2, reverse/1,
- nth/2, nthtail/2, prefix/2, suffix/2, last/1,
+ nth/2, nthtail/2, prefix/2, suffix/2, droplast/1, last/1,
seq/2, seq/3, sum/1, duplicate/2, min/1, max/1, sublist/2, sublist/3,
delete/2,
unzip/1, unzip3/1, zip/2, zip3/3, zipwith/3, zipwith3/4,
@@ -203,6 +203,19 @@ suffix(Suffix, List) ->
Delta = length(List) - length(Suffix),
Delta >= 0 andalso nthtail(Delta, List) =:= Suffix.
+%% droplast(List) returns the list dropping its last element
+
+-spec droplast(List) -> InitList when
+ List :: [T, ...],
+ InitList :: [T],
+ T :: term().
+
+%% This is the simple recursive implementation
+%% reverse(tl(reverse(L))) is faster on average,
+%% but creates more garbage.
+droplast([_T]) -> [];
+droplast([H|T]) -> [H|droplast(T)].
+
%% last(List) returns the last element in a list.
-spec last(List) -> Last when
diff --git a/lib/stdlib/src/log_mf_h.erl b/lib/stdlib/src/log_mf_h.erl
index 19b555a48c..6b42363979 100644
--- a/lib/stdlib/src/log_mf_h.erl
+++ b/lib/stdlib/src/log_mf_h.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2012. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2013. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -135,7 +135,12 @@ handle_event(Event, State) ->
State#state{cur_fd = NewFd, curF = NewF, curB = 0}
end,
[Hi,Lo] = put_int16(Size),
- file:write(NewState#state.cur_fd, [Hi, Lo, Bin]),
+ case file:write(NewState#state.cur_fd, [Hi, Lo, Bin]) of
+ ok ->
+ ok;
+ {error, Reason} ->
+ exit({file_exit, Reason})
+ end,
{ok, NewState#state{curB = NewState#state.curB + Size + 2}};
_ ->
{ok, State}
@@ -174,7 +179,7 @@ file_open(Dir, FileNo) ->
write_index_file(Dir, FileNo),
{ok, Fd};
_ ->
- exit({file, open})
+ exit(file_open)
end.
put_int16(I) ->
@@ -211,7 +216,7 @@ write_index_file(Dir, Index) ->
ok = file:close(Fd),
ok = file:rename(TmpFile,File),
ok;
- _ -> exit(open_index_file)
+ _ -> exit(write_index_file)
end.
inc(N, Max) ->
diff --git a/lib/stdlib/src/maps.erl b/lib/stdlib/src/maps.erl
new file mode 100644
index 0000000000..ba4d6a5c87
--- /dev/null
+++ b/lib/stdlib/src/maps.erl
@@ -0,0 +1,214 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2013. All Rights Reserved.
+%%
+%% The contents of this file are subject to the Erlang Public License,
+%% Version 1.1, (the "License"); you may not use this file except in
+%% compliance with the License. You should have received a copy of the
+%% Erlang Public License along with this software. If not, it can be
+%% retrieved online at http://www.erlang.org/.
+%%
+%% Software distributed under the License is distributed on an "AS IS"
+%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
+%% the License for the specific language governing rights and limitations
+%% under the License.
+%%
+%% %CopyrightEnd%
+%%
+
+-module(maps).
+
+-export([
+ fold/3,
+ map/2,
+ size/1,
+ without/2,
+ with/2,
+ get/3
+ ]).
+
+
+%%% BIFs
+-export([
+ get/2,
+ find/2,
+ from_list/1,
+ is_key/2,
+ keys/1,
+ merge/2,
+ new/0,
+ put/3,
+ remove/2,
+ to_list/1,
+ update/3,
+ values/1
+ ]).
+
+-spec get(Key,Map) -> Value when
+ Key :: term(),
+ Map :: map(),
+ Value :: term().
+
+get(_,_) -> erlang:nif_error(undef).
+
+
+-spec find(Key,Map) -> {ok, Value} | error when
+ Key :: term(),
+ Map :: map(),
+ Value :: term().
+
+find(_,_) -> erlang:nif_error(undef).
+
+
+-spec from_list(List) -> Map when
+ List :: [{Key,Value}],
+ Key :: term(),
+ Value :: term(),
+ Map :: map().
+
+from_list(_) -> erlang:nif_error(undef).
+
+
+-spec is_key(Key,Map) -> boolean() when
+ Key :: term(),
+ Map :: map().
+
+is_key(_,_) -> erlang:nif_error(undef).
+
+
+-spec keys(Map) -> Keys when
+ Map :: map(),
+ Keys :: [Key],
+ Key :: term().
+
+keys(_) -> erlang:nif_error(undef).
+
+
+-spec merge(Map1,Map2) -> Map3 when
+ Map1 :: map(),
+ Map2 :: map(),
+ Map3 :: map().
+
+merge(_,_) -> erlang:nif_error(undef).
+
+
+
+-spec new() -> Map when
+ Map :: map().
+
+new() -> erlang:nif_error(undef).
+
+
+-spec put(Key,Value,Map1) -> Map2 when
+ Key :: term(),
+ Value :: term(),
+ Map1 :: map(),
+ Map2 :: map().
+
+put(_,_,_) -> erlang:nif_error(undef).
+
+
+-spec remove(Key,Map1) -> Map2 when
+ Key :: term(),
+ Map1 :: map(),
+ Map2 :: map().
+
+remove(_,_) -> erlang:nif_error(undef).
+
+
+-spec to_list(Map) -> [{Key,Value}] when
+ Map :: map(),
+ Key :: term(),
+ Value :: term().
+
+to_list(_) -> erlang:nif_error(undef).
+
+
+-spec update(Key,Value,Map1) -> Map2 when
+ Key :: term(),
+ Value :: term(),
+ Map1 :: map(),
+ Map2 :: map().
+
+update(_,_,_) -> erlang:nif_error(undef).
+
+
+-spec values(Map) -> Values when
+ Map :: map(),
+ Values :: [Value],
+ Value :: term().
+
+values(_) -> erlang:nif_error(undef).
+
+
+%%% End of BIFs
+
+-spec get(Key, Map, Default) -> Value | Default when
+ Key :: term(),
+ Map :: map(),
+ Value :: term(),
+ Default :: term().
+
+get(Key, Map, Default) ->
+ case maps:find(Key, Map) of
+ {ok, Value} ->
+ Value;
+ error ->
+ Default
+ end.
+
+
+-spec fold(Fun,Init,Map) -> Acc when
+ Fun :: fun((K, V, AccIn) -> AccOut),
+ Init :: term(),
+ Acc :: term(),
+ AccIn :: term(),
+ AccOut :: term(),
+ Map :: map(),
+ K :: term(),
+ V :: term().
+
+fold(Fun, Init, Map) when is_function(Fun,3), is_map(Map) ->
+ lists:foldl(fun({K,V},A) -> Fun(K,V,A) end,Init,maps:to_list(Map)).
+
+-spec map(Fun,Map1) -> Map2 when
+ Fun :: fun((K, V1) -> V2),
+ Map1 :: map(),
+ Map2 :: map(),
+ K :: term(),
+ V1 :: term(),
+ V2 :: term().
+
+map(Fun, Map) when is_function(Fun, 2), is_map(Map) ->
+ maps:from_list(lists:map(fun
+ ({K,V}) ->
+ {K,Fun(K,V)}
+ end,maps:to_list(Map))).
+
+
+-spec size(Map) -> non_neg_integer() when
+ Map :: map().
+
+size(Map) when is_map(Map) ->
+ erlang:map_size(Map).
+
+
+-spec without(Ks,Map1) -> Map2 when
+ Ks :: [K],
+ Map1 :: map(),
+ Map2 :: map(),
+ K :: term().
+
+without(Ks, M) when is_list(Ks), is_map(M) ->
+ maps:from_list([{K,V}||{K,V} <- maps:to_list(M), not lists:member(K, Ks)]).
+
+
+-spec with(Ks, Map1) -> Map2 when
+ Ks :: [K],
+ Map1 :: map(),
+ Map2 :: map(),
+ K :: term().
+
+with(Ks, M) when is_list(Ks), is_map(M) ->
+ maps:from_list([{K,V}||{K,V} <- maps:to_list(M), lists:member(K, Ks)]).
diff --git a/lib/stdlib/src/ms_transform.erl b/lib/stdlib/src/ms_transform.erl
index 4e2ce39ec2..97564e2e44 100644
--- a/lib/stdlib/src/ms_transform.erl
+++ b/lib/stdlib/src/ms_transform.erl
@@ -369,6 +369,13 @@ copy({var,_Line,Name} = VarDef,Bound) ->
copy({'fun',Line,{clauses,Clauses}},Bound) -> % Dont export bindings from funs
{NewClauses,_IgnoredBindings} = copy_list(Clauses,Bound),
{{'fun',Line,{clauses,NewClauses}},Bound};
+copy({named_fun,Line,Name,Clauses},Bound) -> % Dont export bindings from funs
+ Bound1 = case Name of
+ '_' -> Bound;
+ Name -> gb_sets:add(Name,Bound)
+ end,
+ {NewClauses,_IgnoredBindings} = copy_list(Clauses,Bound1),
+ {{named_fun,Line,Name,NewClauses},Bound};
copy({'case',Line,Of,ClausesList},Bound) -> % Dont export bindings from funs
{NewOf,NewBind0} = copy(Of,Bound),
{NewClausesList,NewBindings} = copy_case_clauses(ClausesList,NewBind0,[]),
@@ -718,10 +725,10 @@ transform_head([V],OuterBound) ->
th(NewV,NewBind,OuterBound).
-toplevel_head_match({match,Line,{var,_,VName},Expr},B,OB) ->
+toplevel_head_match({match,_,{var,Line,VName},Expr},B,OB) ->
warn_var_clash(Line,VName,OB),
{Expr,new_bind({VName,'$_'},B)};
-toplevel_head_match({match,Line,Expr,{var,_,VName}},B,OB) ->
+toplevel_head_match({match,_,Expr,{var,Line,VName}},B,OB) ->
warn_var_clash(Line,VName,OB),
{Expr,new_bind({VName,'$_'},B)};
toplevel_head_match(Other,B,_OB) ->
@@ -903,6 +910,7 @@ bool_test(is_pid,1) -> true;
bool_test(is_port,1) -> true;
bool_test(is_reference,1) -> true;
bool_test(is_tuple,1) -> true;
+bool_test(is_map,1) -> true;
bool_test(is_binary,1) -> true;
bool_test(is_function,1) -> true;
bool_test(is_record,2) -> true;
@@ -917,6 +925,7 @@ real_guard_function(node,0) -> true;
real_guard_function(node,1) -> true;
real_guard_function(round,1) -> true;
real_guard_function(size,1) -> true;
+real_guard_function(map_size,1) -> true;
real_guard_function(tl,1) -> true;
real_guard_function(trunc,1) -> true;
real_guard_function(self,0) -> true;
diff --git a/lib/stdlib/src/orddict.erl b/lib/stdlib/src/orddict.erl
index 45d3c84b3e..c98d78b34d 100644
--- a/lib/stdlib/src/orddict.erl
+++ b/lib/stdlib/src/orddict.erl
@@ -20,7 +20,7 @@
-module(orddict).
%% Standard interface.
--export([new/0,is_key/2,to_list/1,from_list/1,size/1]).
+-export([new/0,is_key/2,to_list/1,from_list/1,size/1,is_empty/1]).
-export([fetch/2,find/2,fetch_keys/1,erase/2]).
-export([store/3,append/3,append_list/3,update/3,update/4,update_counter/3]).
-export([fold/3,map/2,filter/2,merge/3]).
@@ -56,14 +56,22 @@ to_list(Dict) -> Dict.
List :: [{Key :: term(), Value :: term()}],
Orddict :: orddict().
+from_list([]) -> [];
+from_list([{_,_}]=Pair) -> Pair;
from_list(Pairs) ->
- lists:foldl(fun ({K,V}, D) -> store(K, V, D) end, [], Pairs).
+ lists:ukeysort(1, reverse_pairs(Pairs, [])).
-spec size(Orddict) -> non_neg_integer() when
Orddict :: orddict().
size(D) -> length(D).
+-spec is_empty(Orddict) -> boolean() when
+ Orddict :: orddict().
+
+is_empty([]) -> true;
+is_empty([_|_]) -> false.
+
-spec fetch(Key, Orddict) -> Value when
Key :: term(),
Value :: term(),
@@ -229,3 +237,7 @@ merge(F, [{K1,V1}|D1], [{_K2,V2}|D2]) -> %K1 == K2
[{K1,F(K1, V1, V2)}|merge(F, D1, D2)];
merge(F, [], D2) when is_function(F, 3) -> D2;
merge(F, D1, []) when is_function(F, 3) -> D1.
+
+reverse_pairs([{_,_}=H|T], Acc) ->
+ reverse_pairs(T, [H|Acc]);
+reverse_pairs([], Acc) -> Acc.
diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl
index cebc9c91bd..6c25beabe9 100644
--- a/lib/stdlib/src/otp_internal.erl
+++ b/lib/stdlib/src/otp_internal.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1999-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1999-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -83,18 +83,18 @@ obsolete_1(crypto, sha_init, 0) ->
{deprecated, {crypto, hash_init, 1}};
obsolete_1(crypto, md4_update, 2) ->
- {deprecated, {crypto, hash_update, 3}};
+ {deprecated, {crypto, hash_update, 2}};
obsolete_1(crypto, md5_update, 2) ->
- {deprecated, {crypto, hash_update, 3}};
+ {deprecated, {crypto, hash_update, 2}};
obsolete_1(crypto, sha_update, 2) ->
- {deprecated, {crypto, hash_update, 3}};
+ {deprecated, {crypto, hash_update, 2}};
obsolete_1(crypto, md4_final, 1) ->
- {deprecated, {crypto, hash_final, 2}};
+ {deprecated, {crypto, hash_final, 1}};
obsolete_1(crypto, md5_final, 1) ->
- {deprecated, {crypto, hash_final, 2}};
+ {deprecated, {crypto, hash_final, 1}};
obsolete_1(crypto, sha_final, 1) ->
- {deprecated, {crypto, hash_final, 2}};
+ {deprecated, {crypto, hash_final, 1}};
obsolete_1(crypto, md5_mac, 2) ->
{deprecated, {crypto, hmac, 3}};
@@ -104,9 +104,9 @@ obsolete_1(crypto, sha_mac, 3) ->
{deprecated, {crypto, hmac, 4}};
obsolete_1(crypto, sha_mac_96, 2) ->
- {deprecated, {crypto, hmac_n, 3}};
+ {deprecated, {crypto, hmac, 4}};
obsolete_1(crypto, md5_mac_96, 2) ->
- {deprecated, {crypto, hmac_n, 3}};
+ {deprecated, {crypto, hmac, 4}};
obsolete_1(crypto, rsa_sign, 2) ->
{deprecated, {crypto, sign, 4}};
@@ -123,9 +123,9 @@ obsolete_1(crypto, dss_sign, 3) ->
{deprecated, {crypto, sign, 4}};
obsolete_1(crypto, dss_verify, 3) ->
- {deprecated, {crypto, verify, 4}};
+ {deprecated, {crypto, verify, 5}};
obsolete_1(crypto, dss_verify, 4) ->
- {deprecated, {crypto, verify, 4}};
+ {deprecated, {crypto, verify, 5}};
obsolete_1(crypto, mod_exp, 3) ->
{deprecated, {crypto, mod_pow, 3}};
@@ -133,7 +133,7 @@ obsolete_1(crypto, mod_exp, 3) ->
obsolete_1(crypto, dh_compute_key, 3) ->
{deprecated, {crypto, compute_key, 4}};
obsolete_1(crypto, dh_generate_key, 1) ->
- {deprecated, {crypto, generate_key, 3}};
+ {deprecated, {crypto, generate_key, 2}};
obsolete_1(crypto, dh_generate_key, 2) ->
{deprecated, {crypto, generate_key, 3}};
@@ -250,12 +250,12 @@ obsolete_1(snmp, N, A) ->
false ->
no;
true ->
- {deprecated, "Deprecated (will be removed in R17B); use snmpa:"++atom_to_list(N)++"/"++
+ {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 R17B); use \"new\" format instead"};
+ {deprecated, "Deprecated; (will be removed in OTP 18); use \"new\" format instead"};
obsolete_1(snmpm, agent_info, 3) ->
{removed, {snmpm, agent_info, 2}, "R16B"};
obsolete_1(snmpm, update_agent_info, 5) ->
@@ -366,23 +366,6 @@ obsolete_1(auth, node_cookie, 1) ->
obsolete_1(auth, node_cookie, 2) ->
{deprecated, "Deprecated; use erlang:set_cookie/2 and net_adm:ping/1 instead"};
-obsolete_1(erlang, is_constant, 1) ->
- {removed, "Removed in R13B"};
-
-%% Added in R12B-0.
-obsolete_1(ssl, port, 1) ->
- {removed, {ssl, sockname, 1}, "R13B"};
-obsolete_1(ssl, accept, A) when A =:= 1; A =:= 2 ->
- {removed, "deprecated; use ssl:transport_accept/1,2 and ssl:ssl_accept/1,2"};
-obsolete_1(erlang, fault, 1) ->
- {removed, {erlang,error,1}, "R13B"};
-obsolete_1(erlang, fault, 2) ->
- {removed, {erlang,error,2}, "R13B"};
-
-%% Added in R12B-2.
-obsolete_1(file, rawopen, 2) ->
- {removed, "deprecated (will be removed in R13B); use file:open/2 with the raw option"};
-
obsolete_1(http, request, 1) -> {removed,{httpc,request,1},"R15B"};
obsolete_1(http, request, 2) -> {removed,{httpc,request,2},"R15B"};
obsolete_1(http, request, 4) -> {removed,{httpc,request,4},"R15B"};
@@ -438,13 +421,13 @@ obsolete_1(ssh_cm, stop_listener, 1) ->
obsolete_1(ssh_cm, session_open, A) when A =:= 2; A =:= 4 ->
{removed,{ssh_connection,session_channel,A},"R14B"};
obsolete_1(ssh_cm, direct_tcpip, A) when A =:= 6; A =:= 8 ->
- {removed,{ssh_connection,direct_tcpip,A}};
+ {removed,{ssh_connection,direct_tcpip,A},"R14B"};
obsolete_1(ssh_cm, tcpip_forward, 3) ->
{removed,{ssh_connection,tcpip_forward,3},"R14B"};
obsolete_1(ssh_cm, cancel_tcpip_forward, 3) ->
{removed,{ssh_connection,cancel_tcpip_forward,3},"R14B"};
obsolete_1(ssh_cm, open_pty, A) when A =:= 3; A =:= 7; A =:= 9 ->
- {removed,{ssh_connection,open_pty,A},"R14"};
+ {removed,{ssh_connection,open_pty,A},"R14B"};
obsolete_1(ssh_cm, setenv, 5) ->
{removed,{ssh_connection,setenv,5},"R14B"};
obsolete_1(ssh_cm, shell, 2) ->
@@ -458,11 +441,11 @@ obsolete_1(ssh_cm, winch, A) when A =:= 4; A =:= 6 ->
obsolete_1(ssh_cm, signal, 3) ->
{removed,{ssh_connection,signal,3},"R14B"};
obsolete_1(ssh_cm, attach, A) when A =:= 2; A =:= 3 ->
- {removed,{ssh,attach,A}};
+ {removed,"no longer useful; removed in R14B"};
obsolete_1(ssh_cm, detach, 2) ->
- {removed,"no longer useful; will be removed in R14B"};
+ {removed,"no longer useful; removed in R14B"};
obsolete_1(ssh_cm, set_user_ack, 4) ->
- {removed,"no longer useful; will be removed in R14B"};
+ {removed,"no longer useful; removed in R14B"};
obsolete_1(ssh_cm, adjust_window, 3) ->
{removed,{ssh_connection,adjust_window,3},"R14B"};
obsolete_1(ssh_cm, close, 2) ->
@@ -478,9 +461,9 @@ obsolete_1(ssh_cm, send_ack, A) when 3 =< A, A =< 5 ->
obsolete_1(ssh_ssh, connect, A) when 1 =< A, A =< 3 ->
{removed,{ssh,shell,A},"R14B"};
obsolete_1(ssh_sshd, listen, A) when 0 =< A, A =< 3 ->
- {removed,{ssh,daemon,[1,2,3]},"R14"};
+ {removed,{ssh,daemon,[1,2,3]},"R14B"};
obsolete_1(ssh_sshd, stop, 1) ->
- {removed,{ssh,stop_listener,1}};
+ {removed,{ssh,stop_listener,1},"R14B"};
%% Added in R13A.
obsolete_1(regexp, _, _) ->
@@ -524,7 +507,7 @@ obsolete_1(docb_xml_check, _, _) ->
%% Added in R15B
obsolete_1(asn1rt, F, _) when F == load_driver; F == unload_driver ->
- {deprecated,"deprecated (will be removed in R16A); has no effect as drivers are no longer used."};
+ {deprecated,"deprecated (will be removed in OTP 18); has no effect as drivers are no longer used"};
obsolete_1(ssl, pid, 1) ->
{removed,"was removed in R16; is no longer needed"};
obsolete_1(inviso, _, _) ->
@@ -532,7 +515,7 @@ obsolete_1(inviso, _, _) ->
%% Added in R15B01.
obsolete_1(gs, _, _) ->
- {deprecated,"the gs application has been deprecated and will be removed in R17; use the wx application instead"};
+ {deprecated,"the gs application has been deprecated and will be removed in OTP 18; use the wx application instead"};
obsolete_1(ssh, sign_data, 2) ->
{deprecated,"deprecated (will be removed in R16A); use public_key:pem_decode/1, public_key:pem_entry_decode/1 "
"and public_key:sign/3 instead"};
@@ -577,6 +560,26 @@ obsolete_1(wxCursor, new, 3) ->
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) ->
+ {deprecated,"deprecated; use Mod:decode/2 instead"};
+obsolete_1(asn1ct, encode, 3) ->
+ {deprecated,"deprecated; use Mod:encode/2 instead"};
+obsolete_1(asn1rt, decode,3) ->
+ {deprecated,"deprecated; use Mod:decode/2 instead"};
+obsolete_1(asn1rt, encode, 2) ->
+ {deprecated,"deprecated; use Mod:encode/2 instead"};
+obsolete_1(asn1rt, encode, 3) ->
+ {deprecated,"deprecated; use Mod:encode/2 instead"};
+obsolete_1(asn1rt, info, 1) ->
+ {deprecated,"deprecated; use Mod:info/0 instead"};
+obsolete_1(asn1rt, utf8_binary_to_list, 1) ->
+ {deprecated,{unicode,characters_to_list,1}};
+obsolete_1(asn1rt, utf8_list_to_binary, 1) ->
+ {deprecated,{unicode,characters_to_binary,1}};
+obsolete_1(pg, _, _) ->
+ {deprecated,"deprecated; will be removed in OTP 18"};
+
obsolete_1(_, _, _) ->
no.
diff --git a/lib/stdlib/src/pg.erl b/lib/stdlib/src/pg.erl
index ee177e4e0b..a41fd329c2 100644
--- a/lib/stdlib/src/pg.erl
+++ b/lib/stdlib/src/pg.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2011. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -17,6 +17,7 @@
%% %CopyrightEnd%
%%
-module(pg).
+-deprecated(module).
%% pg provides a process group facility. Messages
%% can be multicasted to all members in the group
diff --git a/lib/stdlib/src/pool.erl b/lib/stdlib/src/pool.erl
index a5eb191ab2..dfe6318dea 100644
--- a/lib/stdlib/src/pool.erl
+++ b/lib/stdlib/src/pool.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2011. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2013. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -63,7 +63,7 @@ start(Name) ->
Args :: string(),
Nodes :: [node()].
start(Name, Args) when is_atom(Name) ->
- gen_server:start({global, pool_master}, pool, [], []),
+ _ = gen_server:start({global, pool_master}, pool, [], []),
Hosts = net_adm:host_file(),
Nodes = start_nodes(Hosts, Name, Args),
lists:foreach(fun attach/1, Nodes),
diff --git a/lib/stdlib/src/proc_lib.erl b/lib/stdlib/src/proc_lib.erl
index 1eb6fc2e86..bf2a4e7ac5 100644
--- a/lib/stdlib/src/proc_lib.erl
+++ b/lib/stdlib/src/proc_lib.erl
@@ -216,10 +216,8 @@ ensure_link(SpawnOpts) ->
init_p(Parent, Ancestors, Fun) when is_function(Fun) ->
put('$ancestors', [Parent|Ancestors]),
- {module,Mod} = erlang:fun_info(Fun, module),
- {name,Name} = erlang:fun_info(Fun, name),
- {arity,Arity} = erlang:fun_info(Fun, arity),
- put('$initial_call', {Mod,Name,Arity}),
+ Mfa = erlang:fun_info_mfa(Fun),
+ put('$initial_call', Mfa),
try
Fun()
catch
diff --git a/lib/stdlib/src/qlc.erl b/lib/stdlib/src/qlc.erl
index 48f6622565..002032d48d 100644
--- a/lib/stdlib/src/qlc.erl
+++ b/lib/stdlib/src/qlc.erl
@@ -1266,6 +1266,8 @@ abstr_term(Fun, Line) when is_function(Fun) ->
case erl_eval:fun_data(Fun) of
{fun_data, _Bs, Cs} ->
{'fun', Line, {clauses, Cs}};
+ {named_fun_data, _Bs, Name, Cs} ->
+ {named_fun, Line, Name, Cs};
false ->
{name, Name} = erlang:fun_info(Fun, name),
{arity, Arity} = erlang:fun_info(Fun, arity),
diff --git a/lib/stdlib/src/qlc_pt.erl b/lib/stdlib/src/qlc_pt.erl
index 26bc4d1bdf..b6bb758dfb 100644
--- a/lib/stdlib/src/qlc_pt.erl
+++ b/lib/stdlib/src/qlc_pt.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2004-2013. All Rights Reserved.
+%% Copyright Ericsson AB 2004-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -1218,13 +1218,14 @@ lu_skip(ColConstants, FilterData, PatternFrame, PatternVars,
%% column, the filter will not be skipped.
%% (an example: {X=1} <- ..., X =:= 1).
length(D = Cols -- PatternColumns) =:= 1,
- Frame <- SFs,
- begin
+ {{_,Col} = Column, Constants} <- D,
+ %% Check that the following holds for all frames.
+ lists:all(
+ fun(Frame) ->
%% The column is compared/matched against a constant.
%% If there are no more comparisons/matches then
%% the filter can be replaced by the lookup of
%% the constant.
- [{{_,Col} = Column, Constants}] = D,
{VarI, FrameI} = unify_column(Frame, PV, Col, BindFun,
Imported),
VarValues = deref_skip(VarI, FrameI, LookupOp, Imported),
@@ -1253,7 +1254,7 @@ lu_skip(ColConstants, FilterData, PatternFrame, PatternVars,
length(VarValues) =< 1 andalso
(Constants -- LookedUpConstants =:= []) andalso
bindings_is_subset(Frame, F2, Imported)
- end],
+ end, SFs)],
ColFils = family_list(ColFil),
%% The skip tag 'all' means that all filters are covered by the lookup.
%% It does not imply that there is only one generator as is the case
@@ -2540,6 +2541,19 @@ nos({'fun',L,{clauses,Cs}}, S) ->
{clause,Ln,H,G,B}
end || {clause,Ln,H0,G0,B0} <- Cs],
{{'fun',L,{clauses,NCs}}, S};
+nos({named_fun,Loc,Name,Cs}, S) ->
+ {{var,NLoc,NName}, S1} = case Name of
+ '_' ->
+ S;
+ Name ->
+ nos_pattern({var,Loc,Name}, S)
+ end,
+ NCs = [begin
+ {H, S2} = nos_pattern(H0, S1),
+ {[G, B], _} = nos([G0, B0], S2),
+ {clause,CLoc,H,G,B}
+ end || {clause,CLoc,H0,G0,B0} <- Cs],
+ {{named_fun,NLoc,NName,NCs}, S};
nos({lc,L,E0,Qs0}, S) ->
%% QLCs as well as LCs. It is OK to modify LCs as long as they
%% occur within QLCs--the warning messages have already been found
@@ -2713,6 +2727,9 @@ var2const(E) ->
var_map(F, {var, _, _}=V) ->
F(V);
+var_map(F, {named_fun,NLoc,NName,Cs}) ->
+ {var,Loc,Name} = F({var,NLoc,NName}),
+ {named_fun,Loc,Name,var_map(F, Cs)};
var_map(F, T) when is_tuple(T) ->
list_to_tuple(var_map(F, tuple_to_list(T)));
var_map(F, [E | Es]) ->
diff --git a/lib/stdlib/src/queue.erl b/lib/stdlib/src/queue.erl
index 4bbf5de8a5..472d503b99 100644
--- a/lib/stdlib/src/queue.erl
+++ b/lib/stdlib/src/queue.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -32,6 +32,8 @@
-export([cons/2,head/1,tail/1,
snoc/2,last/1,daeh/1,init/1,liat/1,lait/1]).
+-export_type([queue/0, queue/1]).
+
%%--------------------------------------------------------------------------
%% Efficient implementation of double ended fifo queues
%%
@@ -44,10 +46,9 @@
%% that is; the RearList is reversed.
%%
-%% A declaration equivalent to the following is currently hard-coded
-%% in erl_types.erl
-%%
-%% -opaque queue() :: {list(), list()}.
+-opaque queue(Item) :: {list(Item), list(Item)}.
+
+-opaque queue() :: queue(_).
%% Creation, inspection and conversion
@@ -79,7 +80,7 @@ len(Q) ->
erlang:error(badarg, [Q]).
%% O(len(Q))
--spec to_list(Q :: queue()) -> list().
+-spec to_list(Q :: queue(Item)) -> list(Item).
to_list({In,Out}) when is_list(In), is_list(Out) ->
Out++lists:reverse(In, []);
to_list(Q) ->
@@ -88,7 +89,7 @@ to_list(Q) ->
%% Create queue from list
%%
%% O(length(L))
--spec from_list(L :: list()) -> queue().
+-spec from_list(L :: list(Item)) -> queue(Item).
from_list(L) when is_list(L) ->
f2r(L);
from_list(L) ->
@@ -97,7 +98,7 @@ from_list(L) ->
%% Return true or false depending on if element is in queue
%%
%% O(length(Q)) worst case
--spec member(Item :: term(), Q :: queue()) -> boolean().
+-spec member(Item, Q :: queue(Item)) -> boolean().
member(X, {R,F}) when is_list(R), is_list(F) ->
lists:member(X, R) orelse lists:member(X, F);
member(X, Q) ->
@@ -110,7 +111,7 @@ member(X, Q) ->
%% Put at least one element in each list, if it is cheap
%%
%% O(1)
--spec in(Item :: term(), Q1 :: queue()) -> Q2 :: queue().
+-spec in(Item, Q1 :: queue(Item)) -> Q2 :: queue(Item).
in(X, {[_]=In,[]}) ->
{[X], In};
in(X, {In,Out}) when is_list(In), is_list(Out) ->
@@ -122,7 +123,7 @@ in(X, Q) ->
%% Put at least one element in each list, if it is cheap
%%
%% O(1)
--spec in_r(Item :: term(), Q1 :: queue()) -> Q2 :: queue().
+-spec in_r(Item, Q1 :: queue(Item)) -> Q2 :: queue(Item).
in_r(X, {[],[_]=F}) ->
{F,[X]};
in_r(X, {R,F}) when is_list(R), is_list(F) ->
@@ -133,9 +134,9 @@ in_r(X, Q) ->
%% Take from head/front
%%
%% O(1) amortized, O(len(Q)) worst case
--spec out(Q1 :: queue()) ->
- {{value, Item :: term()}, Q2 :: queue()} |
- {empty, Q1 :: queue()}.
+-spec out(Q1 :: queue(Item)) ->
+ {{value, Item}, Q2 :: queue(Item)} |
+ {empty, Q1 :: queue(Item)}.
out({[],[]}=Q) ->
{empty,Q};
out({[V],[]}) ->
@@ -153,9 +154,9 @@ out(Q) ->
%% Take from tail/rear
%%
%% O(1) amortized, O(len(Q)) worst case
--spec out_r(Q1 :: queue()) ->
- {{value, Item :: term()}, Q2 :: queue()} |
- {empty, Q1 :: queue()}.
+-spec out_r(Q1 :: queue(Item)) ->
+ {{value, Item}, Q2 :: queue(Item)} |
+ {empty, Q1 :: queue(Item)}.
out_r({[],[]}=Q) ->
{empty,Q};
out_r({[],[V]}) ->
@@ -176,7 +177,7 @@ out_r(Q) ->
%% Return the first element in the queue
%%
%% O(1) since the queue is supposed to be well formed
--spec get(Q :: queue()) -> Item :: term().
+-spec get(Q :: queue(Item)) -> Item.
get({[],[]}=Q) ->
erlang:error(empty, [Q]);
get({R,F}) when is_list(R), is_list(F) ->
@@ -195,7 +196,7 @@ get([_|R], []) -> % malformed queue -> O(len(Q))
%% Return the last element in the queue
%%
%% O(1) since the queue is supposed to be well formed
--spec get_r(Q :: queue()) -> Item :: term().
+-spec get_r(Q :: queue(Item)) -> Item.
get_r({[],[]}=Q) ->
erlang:error(empty, [Q]);
get_r({[H|_],F}) when is_list(F) ->
@@ -210,7 +211,7 @@ get_r(Q) ->
%% Return the first element in the queue
%%
%% O(1) since the queue is supposed to be well formed
--spec peek(Q :: queue()) -> empty | {value,Item :: term()}.
+-spec peek(Q :: queue(Item)) -> empty | {value, Item}.
peek({[],[]}) ->
empty;
peek({R,[H|_]}) when is_list(R) ->
@@ -225,7 +226,7 @@ peek(Q) ->
%% Return the last element in the queue
%%
%% O(1) since the queue is supposed to be well formed
--spec peek_r(Q :: queue()) -> empty | {value,Item :: term()}.
+-spec peek_r(Q :: queue(Item)) -> empty | {value, Item}.
peek_r({[],[]}) ->
empty;
peek_r({[H|_],F}) when is_list(F) ->
@@ -240,7 +241,7 @@ peek_r(Q) ->
%% Remove the first element and return resulting queue
%%
%% O(1) amortized
--spec drop(Q1 :: queue()) -> Q2 :: queue().
+-spec drop(Q1 :: queue(Item)) -> Q2 :: queue(Item).
drop({[],[]}=Q) ->
erlang:error(empty, [Q]);
drop({[_],[]}) ->
@@ -258,7 +259,7 @@ drop(Q) ->
%% Remove the last element and return resulting queue
%%
%% O(1) amortized
--spec drop_r(Q1 :: queue()) -> Q2 :: queue().
+-spec drop_r(Q1 :: queue(Item)) -> Q2 :: queue(Item).
drop_r({[],[]}=Q) ->
erlang:error(empty, [Q]);
drop_r({[],[_]}) ->
@@ -279,7 +280,7 @@ drop_r(Q) ->
%% Return reversed queue
%%
%% O(1)
--spec reverse(Q1 :: queue()) -> Q2 :: queue().
+-spec reverse(Q1 :: queue(Item)) -> Q2 :: queue(Item).
reverse({R,F}) when is_list(R), is_list(F) ->
{F,R};
reverse(Q) ->
@@ -289,7 +290,7 @@ reverse(Q) ->
%%
%% Q2 empty: O(1)
%% else: O(len(Q1))
--spec join(Q1 :: queue(), Q2 :: queue()) -> Q3 :: queue().
+-spec join(Q1 :: queue(Item), Q2 :: queue(Item)) -> Q3 :: queue(Item).
join({R,F}=Q, {[],[]}) when is_list(R), is_list(F) ->
Q;
join({[],[]}, {R,F}=Q) when is_list(R), is_list(F) ->
@@ -303,8 +304,8 @@ join(Q1, Q2) ->
%%
%% N = 0..len(Q)
%% O(max(N, len(Q)))
--spec split(N :: non_neg_integer(), Q1 :: queue()) ->
- {Q2 :: queue(),Q3 :: queue()}.
+-spec split(N :: non_neg_integer(), Q1 :: queue(Item)) ->
+ {Q2 :: queue(Item),Q3 :: queue(Item)}.
split(0, {R,F}=Q) when is_list(R), is_list(F) ->
{{[],[]},Q};
split(N, {R,F}=Q) when is_integer(N), N >= 1, is_list(R), is_list(F) ->
@@ -345,8 +346,8 @@ split_r1_to_f2(N, [X|R1], F1, R2, F2) ->
%%
%% Fun(_) -> List: O(length(List) * len(Q))
%% else: O(len(Q)
--spec filter(Fun, Q1 :: queue()) -> Q2 :: queue() when
- Fun :: fun((Item :: term()) -> boolean() | list()).
+-spec filter(Fun, Q1 :: queue(Item)) -> Q2 :: queue(Item) when
+ Fun :: fun((Item) -> boolean() | list(Item)).
filter(Fun, {R0,F0}) when is_function(Fun, 1), is_list(R0), is_list(F0) ->
F = filter_f(Fun, F0),
R = filter_r(Fun, R0),
@@ -422,7 +423,7 @@ filter_r(Fun, [X|R0]) ->
%% Cons to head
%%
--spec cons(Item :: term(), Q1 :: queue()) -> Q2 :: queue().
+-spec cons(Item, Q1 :: queue(Item)) -> Q2 :: queue(Item).
cons(X, Q) ->
in_r(X, Q).
@@ -431,7 +432,7 @@ cons(X, Q) ->
%% Return the first element in the queue
%%
%% O(1) since the queue is supposed to be well formed
--spec head(Q :: queue()) -> Item :: term().
+-spec head(Q :: queue(Item)) -> Item.
head({[],[]}=Q) ->
erlang:error(empty, [Q]);
head({R,F}) when is_list(R), is_list(F) ->
@@ -441,7 +442,7 @@ head(Q) ->
%% Remove head element and return resulting queue
%%
--spec tail(Q1 :: queue()) -> Q2 :: queue().
+-spec tail(Q1 :: queue(Item)) -> Q2 :: queue(Item).
tail(Q) ->
drop(Q).
@@ -449,22 +450,22 @@ tail(Q) ->
%% Cons to tail
%%
--spec snoc(Q1 :: queue(), Item :: term()) -> Q2 :: queue().
+-spec snoc(Q1 :: queue(Item), Item) -> Q2 :: queue(Item).
snoc(Q, X) ->
in(X, Q).
%% Return last element
--spec daeh(Q :: queue()) -> Item :: term().
+-spec daeh(Q :: queue(Item)) -> Item.
daeh(Q) -> get_r(Q).
--spec last(Q :: queue()) -> Item :: term().
+-spec last(Q :: queue(Item)) -> Item.
last(Q) -> get_r(Q).
%% Remove last element and return resulting queue
--spec liat(Q1 :: queue()) -> Q2 :: queue().
+-spec liat(Q1 :: queue(Item)) -> Q2 :: queue(Item).
liat(Q) -> drop_r(Q).
--spec lait(Q1 :: queue()) -> Q2 :: queue().
+-spec lait(Q1 :: queue(Item)) -> Q2 :: queue(Item).
lait(Q) -> drop_r(Q). %% Oops, mis-spelled 'tail' reversed. Forget this one.
--spec init(Q1 :: queue()) -> Q2 :: queue().
+-spec init(Q1 :: queue(Item)) -> Q2 :: queue(Item).
init(Q) -> drop_r(Q).
%%--------------------------------------------------------------------------
diff --git a/lib/stdlib/src/re.erl b/lib/stdlib/src/re.erl
index c5109ec455..7f3cd8f592 100644
--- a/lib/stdlib/src/re.erl
+++ b/lib/stdlib/src/re.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2008-2012. All Rights Reserved.
+%% Copyright Ericsson AB 2008-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -19,20 +19,20 @@
-module(re).
-export([grun/3,urun/3,ucompile/2,replace/3,replace/4,split/2,split/3]).
-%-opaque mp() :: {re_pattern, _, _, _}.
--type mp() :: {re_pattern, _, _, _}.
+-type mp() :: {re_pattern, _, _, _, _}.
-type nl_spec() :: cr | crlf | lf | anycrlf | any.
-type compile_option() :: unicode | anchored | caseless | dollar_endonly
| dotall | extended | firstline | multiline
| no_auto_capture | dupnames | ungreedy
- | {newline, nl_spec()}| bsr_anycrlf
- | bsr_unicode.
+ | {newline, nl_spec()}
+ | bsr_anycrlf | bsr_unicode
+ | no_start_optimize | ucp | never_utf.
%%% BIFs
--export([compile/1, compile/2, run/2, run/3]).
+-export([compile/1, compile/2, run/2, run/3, inspect/2]).
-spec compile(Regexp) -> {ok, MP} | {error, ErrSpec} when
Regexp :: iodata(),
@@ -63,17 +63,21 @@ run(_, _) ->
-spec run(Subject, RE, Options) -> {match, Captured} |
match |
- nomatch when
+ nomatch |
+ {error, ErrType} when
Subject :: iodata() | unicode:charlist(),
RE :: mp() | iodata() | unicode:charlist(),
Options :: [Option],
- Option :: anchored | global | notbol | noteol | notempty
+ Option :: anchored | global | notbol | noteol | notempty
+ | notempty_atstart | report_errors
| {offset, non_neg_integer()} |
+ {match_limit, non_neg_integer()} |
+ {match_limit_recursion, non_neg_integer()} |
{newline, NLSpec :: nl_spec()} |
bsr_anycrlf | bsr_unicode | {capture, ValueSpec} |
{capture, ValueSpec, Type} | CompileOpt,
Type :: index | list | binary,
- ValueSpec :: all | all_but_first | first | none | ValueList,
+ ValueSpec :: all | all_but_first | all_names | first | none | ValueList,
ValueList :: [ValueID],
ValueID :: integer() | string() | atom(),
CompileOpt :: compile_option(),
@@ -83,11 +87,21 @@ run(_, _) ->
| binary(),
ListConversionData :: string()
| {error, string(), binary()}
- | {incomplete, string(), binary()}.
+ | {incomplete, string(), binary()},
+ ErrType :: match_limit | match_limit_recursion | {compile, CompileErr},
+ CompileErr :: {ErrString :: string(), Position :: non_neg_integer()}.
run(_, _, _) ->
erlang:nif_error(undef).
+-spec inspect(MP,Item) -> {namelist, [ binary() ]} when
+ MP :: mp(),
+ Item :: namelist.
+
+inspect(_,_) ->
+ erlang:nif_error(undef).
+
+
%%% End of BIFs
-spec split(Subject, RE) -> SplitList when
@@ -102,8 +116,10 @@ split(Subject,RE) ->
Subject :: iodata() | unicode:charlist(),
RE :: mp() | iodata() | unicode:charlist(),
Options :: [ Option ],
- Option :: anchored | notbol | noteol | notempty
+ Option :: anchored | notbol | noteol | notempty | notempty_atstart
| {offset, non_neg_integer()} | {newline, nl_spec()}
+ | {match_limit, non_neg_integer()}
+ | {match_limit_recursion, non_neg_integer()}
| bsr_anycrlf | bsr_unicode | {return, ReturnType}
| {parts, NumParts} | group | trim | CompileOpt,
NumParts :: non_neg_integer() | infinity,
@@ -266,7 +282,7 @@ extend_subpatterns([],N) ->
extend_subpatterns([H|T],N) ->
[H | extend_subpatterns(T,N-1)].
-compile_split({re_pattern,N,_,_} = Comp, Options) ->
+compile_split({re_pattern,N,_,_,_} = Comp, Options) ->
{Comp,N,Options};
compile_split(Pat,Options0) when not is_tuple(Pat) ->
Options = lists:filter(fun(O) ->
@@ -275,7 +291,7 @@ compile_split(Pat,Options0) when not is_tuple(Pat) ->
case re:compile(Pat,Options) of
{error,Err} ->
{error,Err};
- {ok, {re_pattern,N,_,_} = Comp} ->
+ {ok, {re_pattern,N,_,_,_} = Comp} ->
NewOpt = lists:filter(fun(OO) -> (not copt(OO)) end, Options0),
{Comp,N,NewOpt}
end;
@@ -295,8 +311,11 @@ replace(Subject,RE,Replacement) ->
RE :: mp() | iodata() | unicode:charlist(),
Replacement :: iodata() | unicode:charlist(),
Options :: [Option],
- Option :: anchored | global | notbol | noteol | notempty
+ Option :: anchored | global | notbol | noteol | notempty
+ | notempty_atstart
| {offset, non_neg_integer()} | {newline, NLSpec} | bsr_anycrlf
+ | {match_limit, non_neg_integer()}
+ | {match_limit_recursion, non_neg_integer()}
| bsr_unicode | {return, ReturnType} | CompileOpt,
ReturnType :: iodata | list | binary,
CompileOpt :: compile_option(),
@@ -352,6 +371,8 @@ process_repl_params([],Convert,Unicode) ->
process_repl_params([unicode|T],C,_U) ->
{NT,NC,NU} = process_repl_params(T,C,true),
{[unicode|NT],NC,NU};
+process_repl_params([report_errors|_],_,_) ->
+ throw(badopt);
process_repl_params([{capture,_,_}|_],_,_) ->
throw(badopt);
process_repl_params([{capture,_}|_],_,_) ->
@@ -387,6 +408,8 @@ process_split_params([group|T],C,U,L,S,_G) ->
process_split_params(T,C,U,L,S,true);
process_split_params([global|_],_,_,_,_,_) ->
throw(badopt);
+process_split_params([report_errors|_],_,_,_,_,_) ->
+ throw(badopt);
process_split_params([{capture,_,_}|_],_,_,_,_,_) ->
throw(badopt);
process_split_params([{capture,_}|_],_,_,_,_,_) ->
@@ -487,17 +510,31 @@ do_replace(Subject,Repl,SubExprs0) ->
end || Part <- Repl ].
-check_for_unicode({re_pattern,_,1,_},_) ->
+check_for_unicode({re_pattern,_,1,_,_},_) ->
true;
-check_for_unicode({re_pattern,_,0,_},_) ->
+check_for_unicode({re_pattern,_,0,_,_},_) ->
false;
check_for_unicode(_,L) ->
lists:member(unicode,L).
+
+check_for_crlf({re_pattern,_,_,1,_},_) ->
+ true;
+check_for_crlf({re_pattern,_,_,0,_},_) ->
+ false;
+check_for_crlf(_,L) ->
+ case lists:keysearch(newline,1,L) of
+ {value,{newline,any}} -> true;
+ {value,{newline,crlf}} -> true;
+ {value,{newline,anycrlf}} -> true;
+ _ -> false
+ end.
% SelectReturn = false | all | stirpfirst | none
% ConvertReturn = index | list | binary
% {capture, all} -> all (untouchded)
-% {capture, first} -> kept in argumentt list and Select all
+% {capture, all_names} -> if names are present: treated as a name {capture, [...]}
+% else: same as {capture, []}
+% {capture, first} -> kept in argument list and Select all
% {capture, all_but_first} -> removed from argument list and selects stripfirst
% {capture, none} -> removed from argument list and selects none
% {capture, []} -> removed from argument list and selects none
@@ -506,23 +543,30 @@ check_for_unicode(_,L) ->
% Call as process_parameters([],0,false,index,NeedClean)
-process_parameters([],InitialOffset, SelectReturn, ConvertReturn,_) ->
+process_parameters([],InitialOffset, SelectReturn, ConvertReturn,_,_) ->
{[], InitialOffset, SelectReturn, ConvertReturn};
-process_parameters([{offset, N} | T],_Init0,Select0,Return0,CC) ->
- process_parameters(T,N,Select0,Return0,CC);
-process_parameters([global | T],Init0,Select0,Return0,CC) ->
- process_parameters(T,Init0,Select0,Return0,CC);
-process_parameters([{capture,Values,Type}|T],Init0,Select0,_Return0,CC) ->
- process_parameters([{capture,Values}|T],Init0,Select0,Type,CC);
-process_parameters([{capture,Values}|T],Init0,Select0,Return0,CC) ->
+process_parameters([{offset, N} | T],_Init0,Select0,Return0,CC,RE) ->
+ process_parameters(T,N,Select0,Return0,CC,RE);
+process_parameters([global | T],Init0,Select0,Return0,CC,RE) ->
+ process_parameters(T,Init0,Select0,Return0,CC,RE);
+process_parameters([{capture,Values,Type}|T],Init0,Select0,_Return0,CC,RE) ->
+ process_parameters([{capture,Values}|T],Init0,Select0,Type,CC,RE);
+process_parameters([{capture,Values}|T],Init0,Select0,Return0,CC,RE) ->
% First process the rest to see if capture was already present
{NewTail, Init1, Select1, Return1} =
- process_parameters(T,Init0,Select0,Return0,CC),
+ process_parameters(T,Init0,Select0,Return0,CC,RE),
case Select1 of
false ->
case Values of
all ->
{[{capture,all} | NewTail], Init1, all, Return0};
+ all_names ->
+ case re:inspect(RE,namelist) of
+ {namelist, []} ->
+ {[{capture,first} | NewTail], Init1, none, Return0};
+ {namelist, List} ->
+ {[{capture,[0|List]} | NewTail], Init1, stripfirst, Return0}
+ end;
first ->
{[{capture,first} | NewTail], Init1, all, Return0};
all_but_first ->
@@ -541,20 +585,20 @@ process_parameters([{capture,Values}|T],Init0,Select0,Return0,CC) ->
% Found overriding further down list, ignore this one
{NewTail, Init1, Select1, Return1}
end;
-process_parameters([H|T],Init0,Select0,Return0,true) ->
+process_parameters([H|T],Init0,Select0,Return0,true,RE) ->
case copt(H) of
true ->
- process_parameters(T,Init0,Select0,Return0,true);
+ process_parameters(T,Init0,Select0,Return0,true,RE);
false ->
{NewT,Init,Select,Return} =
- process_parameters(T,Init0,Select0,Return0,true),
+ process_parameters(T,Init0,Select0,Return0,true,RE),
{[H|NewT],Init,Select,Return}
end;
-process_parameters([H|T],Init0,Select0,Return0,false) ->
+process_parameters([H|T],Init0,Select0,Return0,false,RE) ->
{NewT,Init,Select,Return} =
- process_parameters(T,Init0,Select0,Return0,false),
+ process_parameters(T,Init0,Select0,Return0,false,RE),
{[H|NewT],Init,Select,Return};
-process_parameters(_,_,_,_,_) ->
+process_parameters(_,_,_,_,_,_) ->
throw(badlist).
postprocess({match,[]},_,_,_,_) ->
@@ -662,7 +706,7 @@ urun2(Subject0,RE0,Options0) ->
RE = case RE0 of
BinRE when is_binary(BinRE) ->
BinRE;
- {re_pattern,_,_,_} = ReCompiled ->
+ {re_pattern,_,_,_,_} = ReCompiled ->
ReCompiled;
ListRE ->
unicode:characters_to_binary(ListRE,unicode)
@@ -703,38 +747,46 @@ grun(Subject,RE,{Options,NeedClean,OrigRE}) ->
grun2(Subject,RE,{Options,NeedClean}) ->
Unicode = check_for_unicode(RE,Options),
+ CRLF = check_for_crlf(RE,Options),
FlatSubject = to_binary(Subject, Unicode),
- do_grun(FlatSubject,Subject,Unicode,RE,{Options,NeedClean}).
+ do_grun(FlatSubject,Subject,Unicode,CRLF,RE,{Options,NeedClean}).
-do_grun(FlatSubject,Subject,Unicode,RE,{Options0,NeedClean}) ->
+do_grun(FlatSubject,Subject,Unicode,CRLF,RE,{Options0,NeedClean}) ->
{StrippedOptions, InitialOffset,
SelectReturn, ConvertReturn} =
case (catch
- process_parameters(Options0, 0, false, index, NeedClean)) of
+ process_parameters(Options0, 0, false, index, NeedClean,RE)) of
badlist ->
erlang:error(badarg,[Subject,RE,Options0]);
CorrectReturn ->
CorrectReturn
end,
- postprocess(loopexec(FlatSubject,RE,InitialOffset,
- byte_size(FlatSubject),
- Unicode,StrippedOptions),
- SelectReturn,ConvertReturn,FlatSubject,Unicode).
+ try
+ postprocess(loopexec(FlatSubject,RE,InitialOffset,
+ byte_size(FlatSubject),
+ Unicode,CRLF,StrippedOptions),
+ SelectReturn,ConvertReturn,FlatSubject,Unicode)
+ catch
+ throw:ErrTuple ->
+ ErrTuple
+ end.
-loopexec(_,_,X,Y,_,_) when X > Y ->
+loopexec(_,_,X,Y,_,_,_) when X > Y ->
{match,[]};
-loopexec(Subject,RE,X,Y,Unicode,Options) ->
+loopexec(Subject,RE,X,Y,Unicode,CRLF,Options) ->
case re:run(Subject,RE,[{offset,X}]++Options) of
+ {error, Err} ->
+ throw({error,Err});
nomatch ->
{match,[]};
{match,[{A,B}|More]} ->
{match,Rest} =
case B>0 of
true ->
- loopexec(Subject,RE,A+B,Y,Unicode,Options);
+ loopexec(Subject,RE,A+B,Y,Unicode,CRLF,Options);
false ->
{match,M} =
- case re:run(Subject,RE,[{offset,X},notempty,
+ case re:run(Subject,RE,[{offset,X},notempty_atstart,
anchored]++Options) of
nomatch ->
{match,[]};
@@ -745,10 +797,10 @@ loopexec(Subject,RE,X,Y,Unicode,Options) ->
[{_,NStep}|_] when NStep > 0 ->
A+NStep;
_ ->
- forward(Subject,A,1,Unicode)
+ forward(Subject,A,1,Unicode,CRLF)
end,
{match,MM} = loopexec(Subject,RE,NewA,Y,
- Unicode,Options),
+ Unicode,CRLF,Options),
case M of
[] ->
{match,MM};
@@ -759,11 +811,22 @@ loopexec(Subject,RE,X,Y,Unicode,Options) ->
{match,[[{A,B}|More] | Rest]}
end.
-forward(_Chal,A,0,_) ->
+forward(_Chal,A,0,_,_) ->
A;
-forward(_Chal,A,N,false) ->
- A+N;
-forward(Chal,A,N,true) ->
+forward(Chal,A,N,U,true) ->
+ <<_:A/binary,Tl/binary>> = Chal,
+ case Tl of
+ <<$\r,$\n,_/binary>> ->
+ forward(Chal,A+2,N-1,U,true);
+ _ ->
+ forward2(Chal,A,N,U,true)
+ end;
+forward(Chal,A,N,U,false) ->
+ forward2(Chal,A,N,U,false).
+
+forward2(Chal,A,N,false,CRLF) ->
+ forward(Chal,A+1,N-1,false,CRLF);
+forward2(Chal,A,N,true,CRLF) ->
<<_:A/binary,Tl/binary>> = Chal,
Forw = case Tl of
<<1:1,1:1,0:1,_:5,_/binary>> ->
@@ -775,10 +838,16 @@ forward(Chal,A,N,true) ->
_ ->
1
end,
- forward(Chal,A+Forw,N-1,true).
+ forward(Chal,A+Forw,N-1,true,CRLF).
copt(caseless) ->
true;
+copt(no_start_optimize) ->
+ true;
+copt(never_utf) ->
+ true;
+copt(ucp) ->
+ true;
copt(dollar_endonly) ->
true;
copt(dotall) ->
@@ -809,6 +878,8 @@ copt(_) ->
runopt(notempty) ->
true;
+runopt(notempty_atstart) ->
+ true;
runopt(notbol) ->
true;
runopt(noteol) ->
@@ -821,6 +892,10 @@ runopt({capture,_}) ->
true;
runopt(global) ->
true;
+runopt({match_limit,_}) ->
+ true;
+runopt({match_limit_recursion,_}) ->
+ true;
runopt(_) ->
false.
diff --git a/lib/stdlib/src/sets.erl b/lib/stdlib/src/sets.erl
index e6f05b71d4..167a676281 100644
--- a/lib/stdlib/src/sets.erl
+++ b/lib/stdlib/src/sets.erl
@@ -1,8 +1,7 @@
-%% -*- coding: utf-8 -*-
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2000-2012. All Rights Reserved.
+%% Copyright Ericsson AB 2000-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -44,6 +43,8 @@
-export([subtract/2,is_subset/2]).
-export([fold/3,filter/2]).
+-export_type([set/0, set/1]).
+
%% Note: mk_seg/1 must be changed too if seg_size is changed.
-define(seg_size, 16).
-define(max_seg, 32).
@@ -54,8 +55,8 @@
%%------------------------------------------------------------------------------
--type seg() :: tuple().
--type segs() :: tuple().
+-type seg() :: tuple().
+-type segs(_Element) :: tuple().
%% Define a hash set. The default values are the standard ones.
-record(set,
@@ -66,14 +67,12 @@
exp_size=?exp_size :: non_neg_integer(), % Size to expand at
con_size=?con_size :: non_neg_integer(), % Size to contract at
empty :: seg(), % Empty segment
- segs :: segs() % Segments
+ segs :: segs(_) % Segments
}).
-%% A declaration equivalent to the following one is hard-coded in erl_types.
-%% That declaration contains hard-coded information about the #set{}
-%% record and the types of its fields. So, please make sure that any
-%% changes to its structure are also propagated to erl_types.erl.
-%%
-%% -opaque set() :: #set{}.
+
+-opaque set() :: set(_).
+
+-opaque set(Element) :: #set{segs :: segs(Element)}.
%%------------------------------------------------------------------------------
@@ -99,24 +98,23 @@ size(S) -> S#set.size.
%% to_list(Set) -> [Elem].
%% Return the elements in Set as a list.
-spec to_list(Set) -> List when
- Set :: set(),
- List :: [term()].
+ Set :: set(Element),
+ List :: [Element].
to_list(S) ->
fold(fun (Elem, List) -> [Elem|List] end, [], S).
%% from_list([Elem]) -> Set.
%% Build a set from the elements in List.
-spec from_list(List) -> Set when
- List :: [term()],
- Set :: set().
+ List :: [Element],
+ Set :: set(Element).
from_list(L) ->
lists:foldl(fun (E, S) -> add_element(E, S) end, new(), L).
%% is_element(Element, Set) -> boolean().
%% Return 'true' if Element is an element of Set, else 'false'.
-spec is_element(Element, Set) -> boolean() when
- Element :: term(),
- Set :: set().
+ Set :: set(Element).
is_element(E, S) ->
Slot = get_slot(S, E),
Bkt = get_bucket(S, Slot),
@@ -125,9 +123,8 @@ is_element(E, S) ->
%% add_element(Element, Set) -> Set.
%% Return Set with Element inserted in it.
-spec add_element(Element, Set1) -> Set2 when
- Element :: term(),
- Set1 :: set(),
- Set2 :: set().
+ Set1 :: set(Element),
+ Set2 :: set(Element).
add_element(E, S0) ->
Slot = get_slot(S0, E),
{S1,Ic} = on_bucket(fun (B0) -> add_bkt_el(E, B0, B0) end, S0, Slot),
@@ -142,9 +139,8 @@ add_bkt_el(E, [], Bkt) -> {[E|Bkt],1}.
%% del_element(Element, Set) -> Set.
%% Return Set but with Element removed.
-spec del_element(Element, Set1) -> Set2 when
- Element :: term(),
- Set1 :: set(),
- Set2 :: set().
+ Set1 :: set(Element),
+ Set2 :: set(Element).
del_element(E, S0) ->
Slot = get_slot(S0, E),
{S1,Dc} = on_bucket(fun (B0) -> del_bkt_el(E, B0) end, S0, Slot),
@@ -160,9 +156,9 @@ del_bkt_el(_, []) -> {[],0}.
%% union(Set1, Set2) -> Set
%% Return the union of Set1 and Set2.
-spec union(Set1, Set2) -> Set3 when
- Set1 :: set(),
- Set2 :: set(),
- Set3 :: set().
+ Set1 :: set(Element),
+ Set2 :: set(Element),
+ Set3 :: set(Element).
union(S1, S2) when S1#set.size < S2#set.size ->
fold(fun (E, S) -> add_element(E, S) end, S2, S1);
union(S1, S2) ->
@@ -171,14 +167,14 @@ union(S1, S2) ->
%% union([Set]) -> Set
%% Return the union of the list of sets.
-spec union(SetList) -> Set when
- SetList :: [set()],
- Set :: set().
+ SetList :: [set(Element)],
+ Set :: set(Element).
union([S1,S2|Ss]) ->
union1(union(S1, S2), Ss);
union([S]) -> S;
union([]) -> new().
--spec union1(set(), [set()]) -> set().
+-spec union1(set(E), [set(E)]) -> set(E).
union1(S1, [S2|Ss]) ->
union1(union(S1, S2), Ss);
union1(S1, []) -> S1.
@@ -186,9 +182,9 @@ union1(S1, []) -> S1.
%% intersection(Set1, Set2) -> Set.
%% Return the intersection of Set1 and Set2.
-spec intersection(Set1, Set2) -> Set3 when
- Set1 :: set(),
- Set2 :: set(),
- Set3 :: set().
+ Set1 :: set(Element),
+ Set2 :: set(Element),
+ Set3 :: set(Element).
intersection(S1, S2) when S1#set.size < S2#set.size ->
filter(fun (E) -> is_element(E, S2) end, S1);
intersection(S1, S2) ->
@@ -197,13 +193,13 @@ intersection(S1, S2) ->
%% intersection([Set]) -> Set.
%% Return the intersection of the list of sets.
-spec intersection(SetList) -> Set when
- SetList :: [set(),...],
- Set :: set().
+ SetList :: [set(Element),...],
+ Set :: set(Element).
intersection([S1,S2|Ss]) ->
intersection1(intersection(S1, S2), Ss);
intersection([S]) -> S.
--spec intersection1(set(), [set()]) -> set().
+-spec intersection1(set(E), [set(E)]) -> set(E).
intersection1(S1, [S2|Ss]) ->
intersection1(intersection(S1, S2), Ss);
intersection1(S1, []) -> S1.
@@ -211,8 +207,8 @@ intersection1(S1, []) -> S1.
%% is_disjoint(Set1, Set2) -> boolean().
%% Check whether Set1 and Set2 are disjoint.
-spec is_disjoint(Set1, Set2) -> boolean() when
- Set1 :: set(),
- Set2 :: set().
+ Set1 :: set(Element),
+ Set2 :: set(Element).
is_disjoint(S1, S2) when S1#set.size < S2#set.size ->
fold(fun (_, false) -> false;
(E, true) -> not is_element(E, S2)
@@ -226,9 +222,9 @@ is_disjoint(S1, S2) ->
%% Return all and only the elements of Set1 which are not also in
%% Set2.
-spec subtract(Set1, Set2) -> Set3 when
- Set1 :: set(),
- Set2 :: set(),
- Set3 :: set().
+ Set1 :: set(Element),
+ Set2 :: set(Element),
+ Set3 :: set(Element).
subtract(S1, S2) ->
filter(fun (E) -> not is_element(E, S2) end, S1).
@@ -236,34 +232,34 @@ subtract(S1, S2) ->
%% Return 'true' when every element of Set1 is also a member of
%% Set2, else 'false'.
-spec is_subset(Set1, Set2) -> boolean() when
- Set1 :: set(),
- Set2 :: set().
+ Set1 :: set(Element),
+ Set2 :: set(Element).
is_subset(S1, S2) ->
fold(fun (E, Sub) -> Sub andalso is_element(E, S2) end, true, S1).
%% fold(Fun, Accumulator, Set) -> Accumulator.
%% Fold function Fun over all elements in Set and return Accumulator.
-spec fold(Function, Acc0, Set) -> Acc1 when
- Function :: fun((E :: term(),AccIn) -> AccOut),
- Set :: set(),
- Acc0 :: T,
- Acc1 :: T,
- AccIn :: T,
- AccOut :: T.
+ Function :: fun((Element, AccIn) -> AccOut),
+ Set :: set(Element),
+ Acc0 :: Acc,
+ Acc1 :: Acc,
+ AccIn :: Acc,
+ AccOut :: Acc.
fold(F, Acc, D) -> fold_set(F, Acc, D).
%% filter(Fun, Set) -> Set.
%% Filter Set with Fun.
-spec filter(Pred, Set1) -> Set2 when
- Pred :: fun((E :: term()) -> boolean()),
- Set1 :: set(),
- Set2 :: set().
+ Pred :: fun((Element) -> boolean()),
+ Set1 :: set(Element),
+ Set2 :: set(Element).
filter(F, D) -> filter_set(F, D).
%% get_slot(Hashdb, Key) -> Slot.
%% Get the slot. First hash on the new range, if we hit a bucket
%% which has not been split use the unsplit buddy bucket.
--spec get_slot(set(), term()) -> non_neg_integer().
+-spec get_slot(set(E), E) -> non_neg_integer().
get_slot(T, Key) ->
H = erlang:phash(Key, T#set.maxn),
if
@@ -277,8 +273,8 @@ get_bucket(T, Slot) -> get_bucket_s(T#set.segs, Slot).
%% on_bucket(Fun, Hashdb, Slot) -> {NewHashDb,Result}.
%% Apply Fun to the bucket in Slot and replace the returned bucket.
--spec on_bucket(fun((_) -> {[_], 0 | 1}), set(), non_neg_integer()) ->
- {set(), 0 | 1}.
+-spec on_bucket(fun((_) -> {[_], 0 | 1}), set(E), non_neg_integer()) ->
+ {set(E), 0 | 1}.
on_bucket(F, T, Slot) ->
SegI = ((Slot-1) div ?seg_size) + 1,
BktI = ((Slot-1) rem ?seg_size) + 1,
@@ -352,7 +348,7 @@ put_bucket_s(Segs, Slot, Bkt) ->
Seg = setelement(BktI, element(SegI, Segs), Bkt),
setelement(SegI, Segs, Seg).
--spec maybe_expand(set(), 0 | 1) -> set().
+-spec maybe_expand(set(E), 0 | 1) -> set(E).
maybe_expand(T0, Ic) when T0#set.size + Ic > T0#set.exp_size ->
T = maybe_expand_segs(T0), %Do we need more segments.
N = T#set.n + 1, %Next slot to expand into
@@ -370,14 +366,14 @@ maybe_expand(T0, Ic) when T0#set.size + Ic > T0#set.exp_size ->
segs = Segs2};
maybe_expand(T, Ic) -> T#set{size = T#set.size + Ic}.
--spec maybe_expand_segs(set()) -> set().
+-spec maybe_expand_segs(set(E)) -> set(E).
maybe_expand_segs(T) when T#set.n =:= T#set.maxn ->
T#set{maxn = 2 * T#set.maxn,
bso = 2 * T#set.bso,
segs = expand_segs(T#set.segs, T#set.empty)};
maybe_expand_segs(T) -> T.
--spec maybe_contract(set(), non_neg_integer()) -> set().
+-spec maybe_contract(set(E), non_neg_integer()) -> set(E).
maybe_contract(T, Dc) when T#set.size - Dc < T#set.con_size,
T#set.n > ?seg_size ->
N = T#set.n,
@@ -396,7 +392,7 @@ maybe_contract(T, Dc) when T#set.size - Dc < T#set.con_size,
segs = Segs2});
maybe_contract(T, Dc) -> T#set{size = T#set.size - Dc}.
--spec maybe_contract_segs(set()) -> set().
+-spec maybe_contract_segs(set(E)) -> set(E).
maybe_contract_segs(T) when T#set.n =:= T#set.bso ->
T#set{maxn = T#set.maxn div 2,
bso = T#set.bso div 2,
@@ -423,7 +419,7 @@ mk_seg(16) -> {[],[],[],[],[],[],[],[],[],[],[],[],[],[],[],[]}.
%% of segments. We special case the powers of 2 upto 32, this should
%% catch most case. N.B. the last element in the segments tuple is
%% an extra element containing a default empty segment.
--spec expand_segs(segs(), seg()) -> segs().
+-spec expand_segs(segs(E), seg()) -> segs(E).
expand_segs({B1}, Empty) ->
{B1,Empty};
expand_segs({B1,B2}, Empty) ->
@@ -441,7 +437,7 @@ expand_segs(Segs, Empty) ->
list_to_tuple(tuple_to_list(Segs)
++ lists:duplicate(tuple_size(Segs), Empty)).
--spec contract_segs(segs()) -> segs().
+-spec contract_segs(segs(E)) -> segs(E).
contract_segs({B1,_}) ->
{B1};
contract_segs({B1,B2,_,_}) ->
diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl
index c6c706c3a7..679c13f0cf 100644
--- a/lib/stdlib/src/shell.erl
+++ b/lib/stdlib/src/shell.erl
@@ -58,7 +58,7 @@ start(NoCtrlG) ->
start(NoCtrlG, false).
start(NoCtrlG, StartSync) ->
- code:ensure_loaded(user_default),
+ _ = code:ensure_loaded(user_default),
spawn(fun() -> server(NoCtrlG, StartSync) end).
%% Find the pid of the current evaluator process.
@@ -371,6 +371,14 @@ expand_expr({bc,L,E,Qs}, C) ->
{bc,L,expand_expr(E, C),expand_quals(Qs, C)};
expand_expr({tuple,L,Elts}, C) ->
{tuple,L,expand_exprs(Elts, C)};
+expand_expr({map,L,Es}, C) ->
+ {map,L,expand_exprs(Es, C)};
+expand_expr({map,L,Arg,Es}, C) ->
+ {map,L,expand_expr(Arg, C),expand_exprs(Es, C)};
+expand_expr({map_field_assoc,L,K,V}, C) ->
+ {map_field_assoc,L,expand_expr(K, C),expand_expr(V, C)};
+expand_expr({map_field_exact,L,K,V}, C) ->
+ {map_field_exact,L,expand_expr(K, C),expand_expr(V, C)};
expand_expr({record_index,L,Name,F}, C) ->
{record_index,L,Name,expand_expr(F, C)};
expand_expr({record,L,Name,Is}, C) ->
@@ -424,6 +432,8 @@ expand_expr({remote,L,M,F}, C) ->
{remote,L,expand_expr(M, C),expand_expr(F, C)};
expand_expr({'fun',L,{clauses,Cs}}, C) ->
{'fun',L,{clauses,expand_exprs(Cs, C)}};
+expand_expr({named_fun,L,Name,Cs}, C) ->
+ {named_fun,L,Name,expand_exprs(Cs, C)};
expand_expr({clause,L,H,G,B}, C) ->
%% Could expand H and G, but then erl_eval has to be changed as well.
{clause,L,H, G, expand_exprs(B, C)};
@@ -677,8 +687,10 @@ exprs([E0|Es], Bs1, RT, Lf, Ef, Bs0, W) ->
if
Es =:= [] ->
VS = pp(V0, 1, RT),
- [io:requests([{put_chars, unicode, VS}, nl]) ||
- W =:= cmd],
+ case W of
+ cmd -> io:requests([{put_chars, unicode, VS}, nl]);
+ pmt -> ok
+ end,
%% Don't send the result back if it will be
%% discarded anyway.
V = if
@@ -1311,6 +1323,11 @@ list_bindings([{Name,Val}|Bs], RT) ->
F = {'fun',0,{clauses,FCs}},
M = {match,0,{var,0,Name},F},
io:fwrite(<<"~ts\n">>, [erl_pp:expr(M, enc())]);
+ {named_fun_data,_FBs,FName,FCs0} ->
+ FCs = expand_value(FCs0), % looks nicer
+ F = {named_fun,0,FName,FCs},
+ M = {match,0,{var,0,Name},F},
+ io:fwrite(<<"~ts\n">>, [erl_pp:expr(M, enc())]);
false ->
Namel = io_lib:fwrite(<<"~s = ">>, [Name]),
Nl = iolist_size(Namel)+1,
diff --git a/lib/stdlib/src/slave.erl b/lib/stdlib/src/slave.erl
index 9c74041f56..1898dc8aba 100644
--- a/lib/stdlib/src/slave.erl
+++ b/lib/stdlib/src/slave.erl
@@ -289,7 +289,11 @@ register_unique_name(Number) ->
%% If the node should run on the local host, there is
%% no need to use rsh.
-mk_cmd(Host, Name, Args, Waiter, Prog) ->
+mk_cmd(Host, Name, Args, Waiter, Prog0) ->
+ Prog = case os:type() of
+ {ose,_} -> mk_ose_prog(Prog0);
+ _ -> quote_progname(Prog0)
+ end,
BasicCmd = lists:concat([Prog,
" -detached -noinput -master ", node(),
" ", long_or_short(), Name, "@", Host,
@@ -309,6 +313,49 @@ mk_cmd(Host, Name, Args, Waiter, Prog) ->
end
end.
+%% On OSE we have to pass the beam arguments directory to the slave
+%% process. To find out what arguments that should be passed on we
+%% make an assumption. All arguments after the last "--" should be
+%% skipped. So given these arguments:
+%% -Muycs256 -A 1 -- -root /mst/ -progname beam.debug.smp -- -home /mst/ -- -kernel inetrc '"/mst/inetrc.conf"' -- -name test@localhost
+%% we send
+%% -Muycs256 -A 1 -- -root /mst/ -progname beam.debug.smp -- -home /mst/ -- -kernel inetrc '"/mst/inetrc.conf"' --
+%% to the slave with whatever other args that are added in mk_cmd.
+mk_ose_prog(Prog) ->
+ SkipTail = fun("--",[]) ->
+ ["--"];
+ (_,[]) ->
+ [];
+ (Arg,Args) ->
+ [Arg," "|Args]
+ end,
+ [Prog,tl(lists:foldr(SkipTail,[],erlang:system_info(emu_args)))].
+
+%% This is an attempt to distinguish between spaces in the program
+%% path and spaces that separate arguments. The program is quoted to
+%% allow spaces in the path.
+%%
+%% Arguments could exist either if the executable is excplicitly given
+%% (through start/5) or if the -program switch to beam is used and
+%% includes arguments (typically done by cerl in OTP test environment
+%% in order to ensure that slave/peer nodes are started with the same
+%% emulator and flags as the test node. The return from lib:progname()
+%% could then typically be '/<full_path_to>/cerl -gcov').
+quote_progname(Progname) ->
+ do_quote_progname(string:tokens(to_list(Progname)," ")).
+
+do_quote_progname([Prog]) ->
+ "\""++Prog++"\"";
+do_quote_progname([Prog,Arg|Args]) ->
+ case os:find_executable(Prog) of
+ false ->
+ do_quote_progname([Prog++" "++Arg | Args]);
+ _ ->
+ %% this one has an executable - we assume the rest are arguments
+ "\""++Prog++"\""++
+ lists:flatten(lists:map(fun(X) -> [" ",X] end, [Arg|Args]))
+ end.
+
%% Give the user an opportunity to run another program,
%% than the "rsh". On HP-UX rsh is called remsh; thus HP users
%% must start erlang as erl -rsh remsh.
diff --git a/lib/stdlib/src/sofs.erl b/lib/stdlib/src/sofs.erl
index 34eb224647..0bd67db100 100644
--- a/lib/stdlib/src/sofs.erl
+++ b/lib/stdlib/src/sofs.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2001-2011. All Rights Reserved.
+%% Copyright Ericsson AB 2001-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -1509,7 +1509,7 @@ family_projection(SetFun, F) when ?IS_SET(F) ->
%%%
-spec(family_to_digraph(Family) -> Graph when
- Graph :: digraph(),
+ Graph :: digraph:graph(),
Family :: family()).
family_to_digraph(F) when ?IS_SET(F) ->
case ?TYPE(F) of
@@ -1519,7 +1519,7 @@ family_to_digraph(F) when ?IS_SET(F) ->
end.
-spec(family_to_digraph(Family, GraphType) -> Graph when
- Graph :: digraph(),
+ Graph :: digraph:graph(),
Family :: family(),
GraphType :: [digraph:d_type()]).
family_to_digraph(F, Type) when ?IS_SET(F) ->
@@ -1541,7 +1541,7 @@ family_to_digraph(F, Type) when ?IS_SET(F) ->
end.
-spec(digraph_to_family(Graph) -> Family when
- Graph :: digraph(),
+ Graph :: digraph:graph(),
Family :: family()).
digraph_to_family(G) ->
case catch digraph_family(G) of
@@ -1550,7 +1550,7 @@ digraph_to_family(G) ->
end.
-spec(digraph_to_family(Graph, Type) -> Family when
- Graph :: digraph(),
+ Graph :: digraph:graph(),
Family :: family(),
Type :: type()).
digraph_to_family(G, T) ->
diff --git a/lib/stdlib/src/stdlib.app.src b/lib/stdlib/src/stdlib.app.src
index a30685e830..aa9899da3b 100644
--- a/lib/stdlib/src/stdlib.app.src
+++ b/lib/stdlib/src/stdlib.app.src
@@ -71,6 +71,7 @@
lib,
lists,
log_mf_h,
+ maps,
math,
ms_transform,
orddict,
@@ -101,5 +102,8 @@
{registered,[timer_server,rsh_starter,take_over_monitor,pool_master,
dets]},
{applications, [kernel]},
- {env, []}]}.
+ {env, []},
+ {runtime_dependencies, ["sasl-2.4","kernel-3.0.2","erts-6.2","crypto-3.3",
+ "compiler-5.0"]}
+]}.
diff --git a/lib/stdlib/src/stdlib.appup.src b/lib/stdlib/src/stdlib.appup.src
index 55c8087475..951dbca68e 100644
--- a/lib/stdlib/src/stdlib.appup.src
+++ b/lib/stdlib/src/stdlib.appup.src
@@ -1,7 +1,7 @@
%% -*- erlang -*-
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1999-2011. All Rights Reserved.
+%% Copyright Ericsson AB 1999-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -16,12 +16,12 @@
%%
%% %CopyrightEnd%
{"%VSN%",
- %% Up from - max two major revisions back
- [{<<"1\\.19(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R16
- {<<"1\\.18(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R15
- {<<"1\\.17(\\.[0-9]+)*">>,[restart_new_emulator]}],%% R14
- %% Down to - max two major revisions back
- [{<<"1\\.19(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R16
- {<<"1\\.18(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R15
- {<<"1\\.17(\\.[0-9]+)*">>,[restart_new_emulator]}] %% R14
+ %% Up from - max one major revision back
+ [{<<"2\\.[1-3](\\.[0-9]+)*">>,[restart_new_emulator]}, %% 17.1-17.3
+ {<<"2\\.0(\\.[0-9]+)*">>,[restart_new_emulator]}, %% 17.0
+ {<<"1\\.19(\\.[0-9]+)*">>,[restart_new_emulator]}],%% R16
+ %% Down to - max one major revision back
+ [{<<"2\\.[1-3](\\.[0-9]+)*">>,[restart_new_emulator]}, %% 17.1-17.3
+ {<<"2\\.0(\\.[0-9]+)*">>,[restart_new_emulator]}, %% 17.0
+ {<<"1\\.19(\\.[0-9]+)*">>,[restart_new_emulator]}] %% R16
}.
diff --git a/lib/stdlib/src/string.erl b/lib/stdlib/src/string.erl
index d0bd0cb26e..f9b083a56d 100644
--- a/lib/stdlib/src/string.erl
+++ b/lib/stdlib/src/string.erl
@@ -1,4 +1,3 @@
-%% -*- coding: utf-8 -*-
%%
%% %CopyrightBegin%
%%
diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl
index 6d8e25b1de..ede2742875 100644
--- a/lib/stdlib/src/supervisor.erl
+++ b/lib/stdlib/src/supervisor.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -45,10 +45,13 @@
-type restart() :: 'permanent' | 'transient' | 'temporary'.
-type shutdown() :: 'brutal_kill' | timeout().
-type worker() :: 'worker' | 'supervisor'.
--type sup_name() :: {'local', Name :: atom()} | {'global', Name :: atom()}.
+-type sup_name() :: {'local', Name :: atom()}
+ | {'global', Name :: atom()}
+ | {'via', Module :: module(), Name :: any()}.
-type sup_ref() :: (Name :: atom())
| {Name :: atom(), Node :: node()}
| {'global', Name :: atom()}
+ | {'via', Module :: module(), Name :: any()}
| pid().
-type child_spec() :: {Id :: child_id(),
StartFunc :: mfargs(),
@@ -74,14 +77,15 @@
modules = [] :: modules()}).
-type child_rec() :: #child{}.
--define(DICT, dict).
+-define(DICTS, dict).
+-define(DICT, dict:dict).
-define(SETS, sets).
--define(SET, set).
+-define(SET, sets:set).
-record(state, {name,
strategy :: strategy(),
children = [] :: [child_rec()],
- dynamics :: ?DICT() | ?SET(),
+ dynamics :: ?DICT(pid(), list()) | ?SET(pid()),
intensity :: non_neg_integer(),
period :: pos_integer(),
restarts = [],
@@ -260,7 +264,7 @@ init_children(State, StartSpec) ->
{ok, NChildren} ->
{ok, State#state{children = NChildren}};
{error, NChildren, Reason} ->
- terminate_children(NChildren, SupName),
+ _ = terminate_children(NChildren, SupName),
{stop, {shutdown, Reason}}
end;
Error ->
@@ -441,7 +445,7 @@ handle_call(which_children, _From, #state{children = [#child{restart_type = RTyp
State) when ?is_simple(State) ->
Reply = lists:map(fun({?restarting(_),_}) -> {undefined,restarting,CT,Mods};
({Pid, _}) -> {undefined, Pid, CT, Mods} end,
- ?DICT:to_list(dynamics_db(RType, State#state.dynamics))),
+ ?DICTS:to_list(dynamics_db(RType, State#state.dynamics))),
{reply, Reply, State};
handle_call(which_children, _From, State) ->
@@ -480,7 +484,7 @@ handle_call(count_children, _From, #state{children = [#child{restart_type = RTy
child_type = CT}]} = State)
when ?is_simple(State) ->
{Active, Count} =
- ?DICT:fold(fun(Pid, _Val, {Alive, Tot}) ->
+ ?DICTS:fold(fun(Pid, _Val, {Alive, Tot}) ->
case is_pid(Pid) andalso is_process_alive(Pid) of
true ->
{Alive+1, Tot +1};
@@ -752,10 +756,16 @@ restart(Child, State) ->
Id = if ?is_simple(State) -> Child#child.pid;
true -> Child#child.name
end,
- timer:apply_after(0,?MODULE,try_again_restart,[self(),Id]),
+ {ok, _TRef} = timer:apply_after(0,
+ ?MODULE,
+ try_again_restart,
+ [self(),Id]),
{ok,NState2};
{try_again, NState2, #child{name=ChName}} ->
- timer:apply_after(0,?MODULE,try_again_restart,[self(),ChName]),
+ {ok, _TRef} = timer:apply_after(0,
+ ?MODULE,
+ try_again_restart,
+ [self(),ChName]),
{ok,NState2};
Other ->
Other
@@ -768,17 +778,17 @@ restart(Child, State) ->
restart(simple_one_for_one, Child, State) ->
#child{pid = OldPid, mfargs = {M, F, A}} = Child,
- Dynamics = ?DICT:erase(OldPid, dynamics_db(Child#child.restart_type,
+ Dynamics = ?DICTS:erase(OldPid, dynamics_db(Child#child.restart_type,
State#state.dynamics)),
case do_start_child_i(M, F, A) of
{ok, Pid} ->
- NState = State#state{dynamics = ?DICT:store(Pid, A, Dynamics)},
+ NState = State#state{dynamics = ?DICTS:store(Pid, A, Dynamics)},
{ok, NState};
{ok, Pid, _Extra} ->
- NState = State#state{dynamics = ?DICT:store(Pid, A, Dynamics)},
+ NState = State#state{dynamics = ?DICTS:store(Pid, A, Dynamics)},
{ok, NState};
{error, Error} ->
- NState = State#state{dynamics = ?DICT:store(restarting(OldPid), A,
+ NState = State#state{dynamics = ?DICTS:store(restarting(OldPid), A,
Dynamics)},
report_error(start_error, Error, Child, State#state.name),
{try_again, NState}
@@ -850,7 +860,7 @@ terminate_children(Children, SupName) ->
%% we do want them to be shut down as many functions from this module
%% use this function to just clear everything.
terminate_children([Child = #child{restart_type=temporary} | Children], SupName, Res) ->
- do_terminate(Child, SupName),
+ _ = do_terminate(Child, SupName),
terminate_children(Children, SupName, Res);
terminate_children([Child | Children], SupName, Res) ->
NChild = do_terminate(Child, SupName),
@@ -971,7 +981,7 @@ terminate_dynamic_children(Child, Dynamics, SupName) ->
wait_dynamic_children(Child, Pids, Sz, TRef, EStack0)
end,
%% Unroll stacked errors and report them
- ?DICT:fold(fun(Reason, Ls, _) ->
+ ?DICTS:fold(fun(Reason, Ls, _) ->
report_error(shutdown_error, Reason,
Child#child{pid=Ls}, SupName)
end, ok, EStack).
@@ -985,22 +995,22 @@ monitor_dynamic_children(#child{restart_type=temporary}, Dynamics) ->
{error, normal} ->
{Pids, EStack};
{error, Reason} ->
- {Pids, ?DICT:append(Reason, P, EStack)}
+ {Pids, ?DICTS:append(Reason, P, EStack)}
end
- end, {?SETS:new(), ?DICT:new()}, Dynamics);
+ end, {?SETS:new(), ?DICTS:new()}, Dynamics);
monitor_dynamic_children(#child{restart_type=RType}, Dynamics) ->
- ?DICT:fold(fun(P, _, {Pids, EStack}) when is_pid(P) ->
+ ?DICTS:fold(fun(P, _, {Pids, EStack}) when is_pid(P) ->
case monitor_child(P) of
ok ->
{?SETS:add_element(P, Pids), EStack};
{error, normal} when RType =/= permanent ->
{Pids, EStack};
{error, Reason} ->
- {Pids, ?DICT:append(Reason, P, EStack)}
+ {Pids, ?DICTS:append(Reason, P, EStack)}
end;
(?restarting(_), _, {Pids, EStack}) ->
{Pids, EStack}
- end, {?SETS:new(), ?DICT:new()}, Dynamics).
+ end, {?SETS:new(), ?DICTS:new()}, Dynamics).
wait_dynamic_children(_Child, _Pids, 0, undefined, EStack) ->
@@ -1008,7 +1018,7 @@ wait_dynamic_children(_Child, _Pids, 0, undefined, EStack) ->
wait_dynamic_children(_Child, _Pids, 0, TRef, EStack) ->
%% If the timer has expired before its cancellation, we must empty the
%% mail-box of the 'timeout'-message.
- erlang:cancel_timer(TRef),
+ _ = erlang:cancel_timer(TRef),
receive
{timeout, TRef, kill} ->
EStack
@@ -1024,7 +1034,7 @@ wait_dynamic_children(#child{shutdown=brutal_kill} = Child, Pids, Sz,
{'DOWN', _MRef, process, Pid, Reason} ->
wait_dynamic_children(Child, ?SETS:del_element(Pid, Pids), Sz-1,
- TRef, ?DICT:append(Reason, Pid, EStack))
+ TRef, ?DICTS:append(Reason, Pid, EStack))
end;
wait_dynamic_children(#child{restart_type=RType} = Child, Pids, Sz,
TRef, EStack) ->
@@ -1039,7 +1049,7 @@ wait_dynamic_children(#child{restart_type=RType} = Child, Pids, Sz,
{'DOWN', _MRef, process, Pid, Reason} ->
wait_dynamic_children(Child, ?SETS:del_element(Pid, Pids), Sz-1,
- TRef, ?DICT:append(Reason, Pid, EStack));
+ TRef, ?DICTS:append(Reason, Pid, EStack));
{timeout, TRef, kill} ->
?SETS:fold(fun(P, _) -> exit(P, kill) end, ok, Pids),
@@ -1064,12 +1074,12 @@ save_child(Child, #state{children = Children} = State) ->
save_dynamic_child(temporary, Pid, _, #state{dynamics = Dynamics} = State) ->
State#state{dynamics = ?SETS:add_element(Pid, dynamics_db(temporary, Dynamics))};
save_dynamic_child(RestartType, Pid, Args, #state{dynamics = Dynamics} = State) ->
- State#state{dynamics = ?DICT:store(Pid, Args, dynamics_db(RestartType, Dynamics))}.
+ State#state{dynamics = ?DICTS:store(Pid, Args, dynamics_db(RestartType, Dynamics))}.
dynamics_db(temporary, undefined) ->
?SETS:new();
dynamics_db(_, undefined) ->
- ?DICT:new();
+ ?DICTS:new();
dynamics_db(_,Dynamics) ->
Dynamics.
@@ -1078,14 +1088,14 @@ dynamic_child_args(Pid, Dynamics) ->
true ->
{ok, undefined};
false ->
- ?DICT:find(Pid, Dynamics)
+ ?DICTS:find(Pid, Dynamics)
end.
state_del_child(#child{pid = Pid, restart_type = temporary}, State) when ?is_simple(State) ->
NDynamics = ?SETS:del_element(Pid, dynamics_db(temporary, State#state.dynamics)),
State#state{dynamics = NDynamics};
state_del_child(#child{pid = Pid, restart_type = RType}, State) when ?is_simple(State) ->
- NDynamics = ?DICT:erase(Pid, dynamics_db(RType, State#state.dynamics)),
+ NDynamics = ?DICTS:erase(Pid, dynamics_db(RType, State#state.dynamics)),
State#state{dynamics = NDynamics};
state_del_child(Child, State) ->
NChildren = del_child(Child#child.name, State#state.children),
@@ -1148,7 +1158,7 @@ is_dynamic_pid(Pid, Dynamics) ->
true ->
?SETS:is_element(Pid, Dynamics);
false ->
- ?DICT:is_key(Pid, Dynamics)
+ ?DICTS:is_key(Pid, Dynamics)
end.
replace_child(Child, State) ->
diff --git a/lib/stdlib/src/supervisor_bridge.erl b/lib/stdlib/src/supervisor_bridge.erl
index e8405ab9a4..ff4502f0b9 100644
--- a/lib/stdlib/src/supervisor_bridge.erl
+++ b/lib/stdlib/src/supervisor_bridge.erl
@@ -101,7 +101,16 @@ handle_cast(_, State) ->
{noreply, State}.
handle_info({'EXIT', Pid, Reason}, State) when State#state.pid =:= Pid ->
- report_error(child_terminated, Reason, State),
+ case Reason of
+ normal ->
+ ok;
+ shutdown ->
+ ok;
+ {shutdown, _Term} ->
+ ok;
+ _ ->
+ report_error(child_terminated, Reason, State)
+ end,
{stop, Reason, State#state{pid = undefined}};
handle_info(_, State) ->
{noreply, State}.
diff --git a/lib/stdlib/src/sys.erl b/lib/stdlib/src/sys.erl
index c186eab940..d3ba09ce82 100644
--- a/lib/stdlib/src/sys.erl
+++ b/lib/stdlib/src/sys.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -46,7 +46,7 @@
{N :: non_neg_integer(),
[{Event :: system_event(),
FuncState :: _,
- FormFunc :: dbg_fun()}]}}
+ FormFunc :: format_fun()}]}}
| {'statistics', {file:date_time(),
{'reductions', non_neg_integer()},
MessagesIn :: non_neg_integer(),
@@ -57,6 +57,10 @@
Event :: system_event(),
ProcState :: _) -> 'done' | (NewFuncState :: _)).
+-type format_fun() :: fun((Device :: io:device() | file:io_device(),
+ Event :: system_event(),
+ Extra :: term()) -> any()).
+
%%-----------------------------------------------------------------
%% System messages
%%-----------------------------------------------------------------
@@ -102,20 +106,31 @@ get_status(Name, Timeout) -> send_system_msg(Name, get_status, Timeout).
-spec get_state(Name) -> State when
Name :: name(),
State :: term().
-get_state(Name) -> send_system_msg(Name, get_state).
+get_state(Name) ->
+ case send_system_msg(Name, get_state) of
+ {error, Reason} -> error(Reason);
+ State -> State
+ end.
-spec get_state(Name, Timeout) -> State when
Name :: name(),
Timeout :: timeout(),
State :: term().
-get_state(Name, Timeout) -> send_system_msg(Name, get_state, Timeout).
+get_state(Name, Timeout) ->
+ case send_system_msg(Name, get_state, Timeout) of
+ {error, Reason} -> error(Reason);
+ State -> State
+ end.
-spec replace_state(Name, StateFun) -> NewState when
Name :: name(),
StateFun :: fun((State :: term()) -> NewState :: term()),
NewState :: term().
replace_state(Name, StateFun) ->
- send_system_msg(Name, {replace_state, StateFun}).
+ case send_system_msg(Name, {replace_state, StateFun}) of
+ {error, Reason} -> error(Reason);
+ State -> State
+ end.
-spec replace_state(Name, StateFun, Timeout) -> NewState when
Name :: name(),
@@ -123,7 +138,10 @@ replace_state(Name, StateFun) ->
Timeout :: timeout(),
NewState :: term().
replace_state(Name, StateFun, Timeout) ->
- send_system_msg(Name, {replace_state, StateFun}, Timeout).
+ case send_system_msg(Name, {replace_state, StateFun}, Timeout) of
+ {error, Reason} -> error(Reason);
+ State -> State
+ end.
-spec change_code(Name, Module, OldVsn, Extra) -> 'ok' | {error, Reason} when
Name :: name(),
@@ -317,10 +335,10 @@ handle_system_msg(Msg, From, Parent, Mod, Debug, Misc, Hib) ->
handle_system_msg(SysState, Msg, From, Parent, Mod, Debug, Misc, Hib) ->
case do_cmd(SysState, Msg, Parent, Mod, Debug, Misc) of
{suspended, Reply, NDebug, NMisc} ->
- gen:reply(From, Reply),
+ _ = gen:reply(From, Reply),
suspend_loop(suspended, Parent, Mod, NDebug, NMisc, Hib);
{running, Reply, NDebug, NMisc} ->
- gen:reply(From, Reply),
+ _ = gen:reply(From, Reply),
Mod:system_continue(Parent, NDebug, NMisc)
end.
@@ -332,7 +350,7 @@ handle_system_msg(SysState, Msg, From, Parent, Mod, Debug, Misc, Hib) ->
%%-----------------------------------------------------------------
-spec handle_debug(Debug, FormFunc, Extra, Event) -> [dbg_opt()] when
Debug :: [dbg_opt()],
- FormFunc :: dbg_fun(),
+ FormFunc :: format_fun(),
Extra :: term(),
Event :: system_event().
handle_debug([{trace, true} | T], FormFunc, State, Event) ->
@@ -390,10 +408,11 @@ do_cmd(_, suspend, _Parent, _Mod, Debug, Misc) ->
{suspended, ok, Debug, Misc};
do_cmd(_, resume, _Parent, _Mod, Debug, Misc) ->
{running, ok, Debug, Misc};
-do_cmd(SysState, get_state, _Parent, _Mod, Debug, {State, Misc}) ->
- {SysState, State, Debug, Misc};
-do_cmd(SysState, replace_state, _Parent, _Mod, Debug, {State, Misc}) ->
- {SysState, State, Debug, Misc};
+do_cmd(SysState, get_state, _Parent, Mod, Debug, Misc) ->
+ {SysState, do_get_state(Mod, Misc), Debug, Misc};
+do_cmd(SysState, {replace_state, StateFun}, _Parent, Mod, Debug, Misc) ->
+ {Res, NMisc} = do_replace_state(StateFun, Mod, Misc),
+ {SysState, Res, Debug, NMisc};
do_cmd(SysState, get_status, Parent, Mod, Debug, Misc) ->
Res = get_status(SysState, Parent, Mod, Debug, Misc),
{SysState, Res, Debug, Misc};
@@ -407,6 +426,40 @@ do_cmd(suspended, {change_code, Module, Vsn, Extra}, _Parent,
do_cmd(SysState, Other, _Parent, _Mod, Debug, Misc) ->
{SysState, {error, {unknown_system_msg, Other}}, Debug, Misc}.
+do_get_state(Mod, Misc) ->
+ case erlang:function_exported(Mod, system_get_state, 1) of
+ true ->
+ try
+ {ok, State} = Mod:system_get_state(Misc),
+ State
+ catch
+ Cl:Exc ->
+ {error, {callback_failed,{Mod,system_get_state},{Cl,Exc}}}
+ end;
+ false ->
+ Misc
+ end.
+
+do_replace_state(StateFun, Mod, Misc) ->
+ case erlang:function_exported(Mod, system_replace_state, 2) of
+ true ->
+ try
+ {ok, State, NMisc} = Mod:system_replace_state(StateFun, Misc),
+ {State, NMisc}
+ catch
+ Cl:Exc ->
+ {{error, {callback_failed,{Mod,system_replace_state},{Cl,Exc}}}, Misc}
+ end;
+ false ->
+ try
+ NMisc = StateFun(Misc),
+ {NMisc, NMisc}
+ catch
+ Cl:Exc ->
+ {{error, {callback_failed,StateFun,{Cl,Exc}}}, Misc}
+ end
+ end.
+
get_status(SysState, Parent, Mod, Debug, Misc) ->
PDict = get(),
FmtMisc =
diff --git a/lib/stdlib/src/timer.erl b/lib/stdlib/src/timer.erl
index 3cf358630f..72a2dd9616 100644
--- a/lib/stdlib/src/timer.erl
+++ b/lib/stdlib/src/timer.erl
@@ -258,7 +258,7 @@ ensure_started() ->
undefined ->
C = {timer_server, {?MODULE, start_link, []}, permanent, 1000,
worker, [?MODULE]},
- supervisor:start_child(kernel_safe_sup, C), % kernel_safe_sup
+ _ = supervisor:start_child(kernel_safe_sup, C),
ok;
_ -> ok
end.
diff --git a/lib/stdlib/src/zip.erl b/lib/stdlib/src/zip.erl
index c40ce8e203..b768c6d0b9 100644
--- a/lib/stdlib/src/zip.erl
+++ b/lib/stdlib/src/zip.erl
@@ -203,8 +203,18 @@
zip_comment_length}).
--type zip_file() :: #zip_file{}.
+-type create_option() :: memory | cooked | verbose | {comment, string()}
+ | {cwd, file:filename()}
+ | {compress, extension_spec()}
+ | {uncompress, extension_spec()}.
+-type extension() :: string().
+-type extension_spec() :: all | [extension()] | {add, [extension()]} | {del, [extension()]}.
+-type filename() :: file:filename().
+
-type zip_comment() :: #zip_comment{}.
+-type zip_file() :: #zip_file{}.
+
+-export_type([create_option/0, filename/0]).
%% Open a zip archive with options
%%
@@ -340,13 +350,13 @@ unzip(F) -> unzip(F, []).
-spec(unzip(Archive, Options) -> RetValue when
Archive :: file:name() | binary(),
Options :: [Option],
- Option :: {file_list, FileList}
+ Option :: {file_list, FileList} | cooked
| keep_old_files | verbose | memory |
{file_filter, FileFilter} | {cwd, CWD},
FileList :: [file:name()],
FileBinList :: [{file:name(),binary()}],
FileFilter :: fun((ZipFile) -> boolean()),
- CWD :: string(),
+ CWD :: file:filename(),
ZipFile :: zip_file(),
RetValue :: {ok, FileList}
| {ok, FileBinList}
@@ -430,7 +440,7 @@ zip(F, Files) -> zip(F, Files, []).
What :: all | [Extension] | {add, [Extension]} | {del, [Extension]},
Extension :: string(),
Comment :: string(),
- CWD :: string(),
+ CWD :: file:filename(),
RetValue :: {ok, FileName :: file:name()}
| {ok, {FileName :: file:name(), binary()}}
| {error, Reason :: term()}).
@@ -712,8 +722,8 @@ table(F, O) -> list_dir(F, O).
FileList :: [FileSpec],
FileSpec :: file:name() | {file:name(), binary()}
| {file:name(), binary(), file:file_info()},
- RetValue :: {ok, FileName :: file:name()}
- | {ok, {FileName :: file:name(), binary()}}
+ RetValue :: {ok, FileName :: filename()}
+ | {ok, {FileName :: filename(), binary()}}
| {error, Reason :: term()}).
create(F, Fs) -> zip(F, Fs).
@@ -724,14 +734,9 @@ create(F, Fs) -> zip(F, Fs).
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 :: string(),
- RetValue :: {ok, FileName :: file:name()}
- | {ok, {FileName :: file:name(), binary()}}
+ Option :: create_option(),
+ RetValue :: {ok, FileName :: filename()}
+ | {ok, {FileName :: filename(), binary()}}
| {error, Reason :: term()}).
create(F, Fs, O) -> zip(F, Fs, O).
@@ -755,7 +760,7 @@ extract(F) -> unzip(F).
FileList :: [file:name()],
FileBinList :: [{file:name(),binary()}],
FileFilter :: fun((ZipFile) -> boolean()),
- CWD :: string(),
+ CWD :: file:filename(),
ZipFile :: zip_file(),
RetValue :: {ok, FileList}
| {ok, FileBinList}
@@ -1153,7 +1158,7 @@ zip_open(Archive) -> zip_open(Archive, []).
Archive :: file:name() | binary(),
ZipHandle :: pid(),
Options :: [Option],
- Option :: cooked | memory | {cwd, CWD :: string()},
+ Option :: cooked | memory | {cwd, CWD :: file:filename()},
Reason :: term()).
zip_open(Archive, Options) ->