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/beam_lib.erl2
-rw-r--r--lib/stdlib/src/c.erl13
-rw-r--r--lib/stdlib/src/dets.erl88
-rw-r--r--lib/stdlib/src/dets_server.erl8
-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.erl10
-rw-r--r--lib/stdlib/src/digraph_utils.erl4
-rw-r--r--lib/stdlib/src/edlin.erl3
-rw-r--r--lib/stdlib/src/epp.erl6
-rw-r--r--lib/stdlib/src/erl_compile.erl225
-rw-r--r--lib/stdlib/src/erl_eval.erl209
-rw-r--r--lib/stdlib/src/erl_expand_records.erl23
-rw-r--r--lib/stdlib/src/erl_internal.erl7
-rw-r--r--lib/stdlib/src/erl_lint.erl110
-rw-r--r--lib/stdlib/src/erl_parse.yrl57
-rw-r--r--lib/stdlib/src/erl_pp.erl20
-rw-r--r--lib/stdlib/src/erl_scan.erl8
-rw-r--r--lib/stdlib/src/erl_tar.erl5
-rw-r--r--lib/stdlib/src/error_logger_tty_h.erl11
-rw-r--r--lib/stdlib/src/escript.erl8
-rw-r--r--lib/stdlib/src/ets.erl63
-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.erl2
-rw-r--r--lib/stdlib/src/gb_sets.erl3
-rw-r--r--lib/stdlib/src/gb_trees.erl3
-rw-r--r--lib/stdlib/src/gen_fsm.erl2
-rw-r--r--lib/stdlib/src/gen_server.erl2
-rw-r--r--lib/stdlib/src/io_lib.erl17
-rw-r--r--lib/stdlib/src/io_lib_pretty.erl34
-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.erl200
-rw-r--r--lib/stdlib/src/ms_transform.erl9
-rw-r--r--lib/stdlib/src/orddict.erl16
-rw-r--r--lib/stdlib/src/pool.erl4
-rw-r--r--lib/stdlib/src/qlc.erl2
-rw-r--r--lib/stdlib/src/qlc_pt.erl16
-rw-r--r--lib/stdlib/src/re.erl176
-rw-r--r--lib/stdlib/src/sets.erl3
-rw-r--r--lib/stdlib/src/shell.erl15
-rw-r--r--lib/stdlib/src/slave.erl28
-rw-r--r--lib/stdlib/src/stdlib.app.src1
-rw-r--r--lib/stdlib/src/stdlib.appup.src14
-rw-r--r--lib/stdlib/src/string.erl1
-rw-r--r--lib/stdlib/src/supervisor.erl16
-rw-r--r--lib/stdlib/src/sys.erl4
-rw-r--r--lib/stdlib/src/timer.erl2
51 files changed, 1248 insertions, 328 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/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/c.erl b/lib/stdlib/src/c.erl
index 6e96e3d564..c2256c0cf9 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
@@ -694,7 +699,7 @@ pwd() ->
Dir :: file:name().
cd(Dir) ->
- file:set_cwd(Dir),
+ _ = file:set_cwd(Dir),
pwd().
%% ls()
@@ -716,7 +721,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..44dad04f43 100644
--- a/lib/stdlib/src/dets.erl
+++ b/lib/stdlib/src/dets.erl
@@ -469,7 +469,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 +1384,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 +1635,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 +1685,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 +1735,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.
@@ -1790,12 +1792,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 +2007,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 +2015,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 +2026,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.
@@ -2123,7 +2129,7 @@ do_open_file([Fname, Verbose], 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),
+ _ = file:delete(OpenArgs#open_args.file),
do_open_file([Tab, OpenArgs, Verb], Parent, Server, Ref);
{error, _Reason} = Error ->
err(Error);
@@ -2671,11 +2677,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 +2736,8 @@ compact(SourceHead) ->
{ok, H} ->
H;
Error ->
- file:close(Fd),
- file:delete(Tmp),
+ _ = file:close(Fd),
+ _ = file:delete(Tmp),
throw(Error)
end,
@@ -2748,12 +2754,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 +2783,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,15 +2824,15 @@ 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.
@@ -2855,13 +2861,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 +2902,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 +2949,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 +3273,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 +3302,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..268c201047 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-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
@@ -241,8 +241,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() ->
@@ -338,7 +338,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..7e198a2469 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-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
@@ -37,7 +36,7 @@
-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]).
@@ -113,6 +112,11 @@ 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(),
diff --git a/lib/stdlib/src/digraph_utils.erl b/lib/stdlib/src/digraph_utils.erl
index 807b5c12a1..0e248df453 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-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
@@ -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..be9a4f5107 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
diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl
index d1d060ebc8..4fd302e612 100644
--- a/lib/stdlib/src/epp.erl
+++ b/lib/stdlib/src/epp.erl
@@ -219,7 +219,7 @@ parse_file(Epp) ->
[{eof,Location}]
end.
--define(DEFAULT_ENCODING, latin1).
+-define(DEFAULT_ENCODING, utf8).
-spec default_encoding() -> source_encoding().
@@ -644,7 +644,7 @@ leave_file(From, St) ->
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,
@@ -1247,6 +1247,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..ed8fea5d78 100644
--- a/lib/stdlib/src/erl_compile.erl
+++ b/lib/stdlib/src/erl_compile.erl
@@ -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);
@@ -67,8 +70,12 @@ compile(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.
@@ -83,66 +90,178 @@ compiler_runner(List) ->
%% 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 +289,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 +336,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..5f96795d92 100644
--- a/lib/stdlib/src/erl_eval.erl
+++ b/lib/stdlib/src/erl_eval.erl
@@ -179,8 +179,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 +239,29 @@ 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_field_assoc,_,EK, EV}, Bs0, Lf, Ef, RBs) ->
+ {value,K,Bs1} = expr(EK, Bs0, Lf, Ef, none),
+ {value,V,Bs2} = expr(EV, Bs0, Lf, Ef, none),
+ ret_expr({map_assoc,K,V}, merge_bindings(Bs1,Bs2), RBs);
+expr({map_field_exact,_,EK, EV}, Bs0, Lf, Ef, RBs) ->
+ {value,K,Bs1} = expr(EK, Bs0, Lf, Ef, none),
+ {value,V,Bs2} = expr(EV, Bs0, Lf, Ef, none),
+ ret_expr({map_exact,K,V}, merge_bindings(Bs1,Bs2), RBs);
+expr({map,_, Binding,Es}, Bs0, Lf, Ef, RBs) ->
+ {value, Map0, Bs1} = expr(Binding, Bs0, Lf, Ef, RBs),
+ {Vs,Bs} = expr_list(Es, Bs1, Lf, Ef),
+ ret_expr(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), Bs, RBs);
+expr({map,_,Es}, Bs0, Lf, Ef, RBs) ->
+ {Vs,Bs} = expr_list(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 +289,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 +609,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 +624,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);
@@ -676,12 +762,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 +785,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)
@@ -910,6 +1017,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 +1099,9 @@ 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({bin, _, Fs}, <<_/bitstring>>=B, Bs0, BBs) ->
eval_bits:match_bits(Fs, B, Bs0, BBs,
match_fun(BBs),
@@ -1034,6 +1145,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..4741bef6b9 100644
--- a/lib/stdlib/src/erl_expand_records.erl
+++ b/lib/stdlib/src/erl_expand_records.erl
@@ -132,6 +132,12 @@ 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,Key,V0}, St0) ->
+ {V,St1} = pattern(V0, St0),
+ {{map_field_exact,Line,Key,V},St1};
%%pattern({struct,Line,Tag,Ps}, St0) ->
%% {TPs,TPsvs,St1} = pattern_list(Ps, St0),
%% {{struct,Line,Tag,TPs},TPsvs,St1};
@@ -301,6 +307,20 @@ 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,Var,Es0}, St0) ->
+ {Es1,St1} = expr_list(Es0, St0),
+ {{map,Line,Var,Es1},St1};
+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};
@@ -344,6 +364,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}},
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..f630db6032 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -225,6 +225,8 @@ 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_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 +234,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 +286,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' "
@@ -842,8 +849,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),
@@ -1147,6 +1155,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_set().
+
+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 +1371,19 @@ 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) ->
+ pattern_list(Ps, Vt, Old, Bvt, St);
+pattern({map_field_assoc,Line,_,_}, _, _, _, St) ->
+ {[],[],add_error(Line, illegal_pattern, St)};
+pattern({map_field_exact,Line,KP,VP}, Vt, Old, Bvt0, St0) ->
+ %% if the key pattern has variables we should fail
+ case expr(KP,[],St0) of
+ {[],_} ->
+ pattern(VP, Vt, Old, Bvt0, St0);
+ {[Var|_],_} ->
+ %% found variables in key expression
+ {Vt,Old,add_error(Line,{illegal_map_key_variable,element(1,Var)},St0)}
+ end;
%%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 +1771,14 @@ 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) ->
+ gexpr_list(Es, Vt, St);
+gexpr({map,_Line,Src,Es}, Vt, St) ->
+ gexpr_list([Src|Es], Vt, St);
+gexpr({map_field_assoc,_Line,K,V}, Vt, St) ->
+ gexpr_list([K,V], Vt, St);
+gexpr({map_field_exact,_Line,K,V}, Vt, St) ->
+ gexpr_list([K,V], Vt, St);
gexpr({record_index,Line,Name,Field}, _Vt, St) ->
check_record(Line, Name, St,
fun (Dfs, St1) -> record_field(Field, Name, Dfs, St1) end );
@@ -1959,6 +1996,24 @@ 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) ->
+ {Rvt,St1} = expr_list(Es,Vt,St),
+ case is_valid_map_construction(Es) of
+ true -> {Rvt,St1};
+ false -> {[],add_error(Line,illegal_map_construction,St1)}
+ end;
+expr({map,_Line,Src,Es}, Vt, St) ->
+ expr_list([Src|Es], Vt, St);
+expr({map_field_assoc,Line,K,V}, Vt, St) ->
+ case is_valid_map_key(K,St) of
+ true -> expr_list([K,V], Vt, St);
+ {false,Var} -> {[],add_error(Line,{illegal_map_key_variable,Var},St)}
+ end;
+expr({map_field_exact,Line,K,V}, Vt, St) ->
+ case is_valid_map_key(K,St) of
+ true -> expr_list([K,V], Vt, St);
+ {false,Var} -> {[],add_error(Line,{illegal_map_key_variable,Var},St)}
+ end;
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 +2083,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)};
@@ -2180,6 +2244,7 @@ is_valid_record(Rec) ->
{lc, _, _, _} -> false;
{record_index, _, _, _} -> false;
{'fun', _, _} -> false;
+ {named_fun, _, _, _} -> false;
_ -> true
end.
@@ -2208,6 +2273,20 @@ is_valid_call(Call) ->
_ -> true
end.
+%% check_map_construction
+%% Only #{ K => V }, i.e. assoc is a valid construction
+is_valid_map_construction([{map_field_assoc,_,_,_}|Es]) ->
+ is_valid_map_construction(Es);
+is_valid_map_construction([]) -> true;
+is_valid_map_construction(_) -> false.
+
+is_valid_map_key(K,St) ->
+ case expr(K,[],St) of
+ {[],_} -> true;
+ {[Var|_],_} ->
+ {false,element(1,Var)}
+ 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.
@@ -2528,6 +2607,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) ->
@@ -2633,6 +2719,7 @@ is_default_type({iodata, 0}) -> true;
is_default_type({iolist, 0}) -> true;
is_default_type({list, 0}) -> true;
is_default_type({list, 1}) -> true;
+is_default_type({map, 0}) -> true;
is_default_type({maybe_improper_list, 0}) -> true;
is_default_type({maybe_improper_list, 2}) -> true;
is_default_type({mfa, 0}) -> true;
@@ -2882,7 +2969,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 +2998,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.
diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl
index 7145b0858f..6316db7054 100644
--- a/lib/stdlib/src/erl_parse.yrl
+++ b/lib/stdlib/src/erl_parse.yrl
@@ -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, []}.
@@ -799,8 +837,15 @@ 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 ->
@@ -850,6 +895,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;
@@ -1050,3 +1101,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..8a1d8e0440 100644
--- a/lib/stdlib/src/erl_pp.erl
+++ b/lib/stdlib/src/erl_pp.erl
@@ -511,10 +511,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 ->
@@ -729,8 +736,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..ae59d5f44f 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);
diff --git a/lib/stdlib/src/erl_tar.erl b/lib/stdlib/src/erl_tar.erl
index 40ef6c8998..40b48d7999 100644
--- a/lib/stdlib/src/erl_tar.erl
+++ b/lib/stdlib/src/erl_tar.erl
@@ -45,10 +45,7 @@ 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,
+ _ = [ram_file:uncompress(File) || Opts =:= [compressed]],
{ok,{read,File}};
Error ->
Error
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..35f6dff57e 100644
--- a/lib/stdlib/src/escript.erl
+++ b/lib/stdlib/src/escript.erl
@@ -771,9 +771,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..cc5e69f574 100644
--- a/lib/stdlib/src/ets.erl
+++ b/lib/stdlib/src/ets.erl
@@ -507,7 +507,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 +719,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 +750,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 +796,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 +896,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 +985,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 +1304,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),
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..a266daa084 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
diff --git a/lib/stdlib/src/gb_sets.erl b/lib/stdlib/src/gb_sets.erl
index ba35a7170a..237317ac94 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-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
diff --git a/lib/stdlib/src/gb_trees.erl b/lib/stdlib/src/gb_trees.erl
index de0c239e26..7a4dfe1a0b 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-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
diff --git a/lib/stdlib/src/gen_fsm.erl b/lib/stdlib/src/gen_fsm.erl
index 9e9d4ee4bb..e9654322f1 100644
--- a/lib/stdlib/src/gen_fsm.erl
+++ b/lib/stdlib/src/gen_fsm.erl
@@ -549,7 +549,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);
diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl
index df68a37c06..5f14e48b0a 100644
--- a/lib/stdlib/src/gen_server.erl
+++ b/lib/stdlib/src/gen_server.erl
@@ -623,7 +623,7 @@ handle_msg({'$gen_call', From, Msg}, Parent, Name, State, Mod, Debug) ->
{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)
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_pretty.erl b/lib/stdlib/src/io_lib_pretty.erl
index 7637ad7a3d..9005fede4d 100644
--- a/lib/stdlib/src/io_lib_pretty.erl
+++ b/lib/stdlib/src/io_lib_pretty.erl
@@ -25,6 +25,8 @@
-export([print/1,print/2,print/3,print/4,print/5,print/6]).
+-compile(no_native).
+
%%%
%%% Exported functions
%%%
@@ -101,6 +103,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 +140,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 +290,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 +342,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 +369,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 +404,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) ->
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..57b5072639
--- /dev/null
+++ b/lib/stdlib/src/maps.erl
@@ -0,0 +1,200 @@
+%%
+%% %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
+ ]).
+
+
+%%% 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
+ ]).
+
+-compile(no_native).
+
+%% Shadowed by erl_bif_types: maps:get/3
+-spec get(Key,Map) -> Value when
+ Key :: term(),
+ Map :: map(),
+ Value :: term().
+
+get(_,_) -> erlang:nif_error(undef).
+
+
+%% Shadowed by erl_bif_types: maps:find/3
+-spec find(Key,Map) -> {ok, Value} | error when
+ Key :: term(),
+ Map :: map(),
+ Value :: term().
+
+find(_,_) -> erlang:nif_error(undef).
+
+
+%% Shadowed by erl_bif_types: maps:from_list/1
+-spec from_list([{Key,Value}]) -> Map when
+ Key :: term(),
+ Value :: term(),
+ Map :: map().
+
+from_list(_) -> erlang:nif_error(undef).
+
+
+%% Shadowed by erl_bif_types: maps:is_key/2
+-spec is_key(Key,Map) -> boolean() when
+ Key :: term(),
+ Map :: map().
+
+is_key(_,_) -> erlang:nif_error(undef).
+
+
+%% Shadowed by erl_bif_types: maps:keys/1
+-spec keys(Map) -> Keys when
+ Map :: map(),
+ Keys :: [Key],
+ Key :: term().
+
+keys(_) -> erlang:nif_error(undef).
+
+
+%% Shadowed by erl_bif_types: maps:merge/2
+-spec merge(Map1,Map2) -> Map3 when
+ Map1 :: map(),
+ Map2 :: map(),
+ Map3 :: map().
+
+merge(_,_) -> erlang:nif_error(undef).
+
+
+
+%% Shadowed by erl_bif_types: maps:new/0
+-spec new() -> Map when
+ Map :: map().
+
+new() -> erlang:nif_error(undef).
+
+
+%% Shadowed by erl_bif_types: maps:put/3
+-spec put(Key,Value,Map1) -> Map2 when
+ Key :: term(),
+ Value :: term(),
+ Map1 :: map(),
+ Map2 :: map().
+
+put(_,_,_) -> erlang:nif_error(undef).
+
+
+%% Shadowed by erl_bif_types: maps:put/3
+-spec remove(Key,Map1) -> Map2 when
+ Key :: term(),
+ Map1 :: map(),
+ Map2 :: map().
+
+remove(_,_) -> erlang:nif_error(undef).
+
+
+%% Shadowed by erl_bif_types: maps:to_list/1
+-spec to_list(Map) -> [{Key,Value}] when
+ Map :: map(),
+ Key :: term(),
+ Value :: term().
+
+to_list(_) -> erlang:nif_error(undef).
+
+
+%% Shadowed by erl_bif_types: maps:update/3
+-spec update(Key,Value,Map1) -> Map2 when
+ Key :: term(),
+ Value :: term(),
+ Map1 :: map(),
+ Map2 :: map().
+
+update(_,_,_) -> erlang:nif_error(undef).
+
+
+%% Shadowed by erl_bif_types: maps:values/1
+-spec values(Map) -> Keys when
+ Map :: map(),
+ Keys :: [Key],
+ Key :: term().
+
+values(_) -> erlang:nif_error(undef).
+
+
+%%% End of BIFs
+
+-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)]).
diff --git a/lib/stdlib/src/ms_transform.erl b/lib/stdlib/src/ms_transform.erl
index 4e2ce39ec2..27dfcf52e1 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,[]),
@@ -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/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/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..c26764eb18 100644
--- a/lib/stdlib/src/qlc_pt.erl
+++ b/lib/stdlib/src/qlc_pt.erl
@@ -2540,6 +2540,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 +2726,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/re.erl b/lib/stdlib/src/re.erl
index c5109ec455..afc63496d0 100644
--- a/lib/stdlib/src/re.erl
+++ b/lib/stdlib/src/re.erl
@@ -19,20 +19,21 @@
-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, _, _, _}.
+%-opaque 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 +64,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 +88,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 +117,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 +283,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 +292,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 +312,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 +372,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 +409,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 +511,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 +544,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 +586,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 +707,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 +748,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 +798,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 +812,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 +839,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 +879,8 @@ copt(_) ->
runopt(notempty) ->
true;
+runopt(notempty_atstart) ->
+ true;
runopt(notbol) ->
true;
runopt(noteol) ->
@@ -821,6 +893,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..ebf011a7d9 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-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
diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl
index c6c706c3a7..3b90542452 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.
@@ -424,6 +424,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 +679,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 +1315,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..3e647635bc 100644
--- a/lib/stdlib/src/slave.erl
+++ b/lib/stdlib/src/slave.erl
@@ -289,7 +289,8 @@ 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 = quote_progname(Prog0),
BasicCmd = lists:concat([Prog,
" -detached -noinput -master ", node(),
" ", long_or_short(), Name, "@", Host,
@@ -309,6 +310,31 @@ mk_cmd(Host, Name, Args, Waiter, Prog) ->
end
end.
+%% 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/stdlib.app.src b/lib/stdlib/src/stdlib.app.src
index a30685e830..a64b8e13c0 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,
diff --git a/lib/stdlib/src/stdlib.appup.src b/lib/stdlib/src/stdlib.appup.src
index 55c8087475..749a9a4201 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-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
@@ -17,11 +17,11 @@
%% %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
+ [{<<"2\\.0(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R17
+ {<<"1\\.19(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R16
+ {<<"1\\.18(\\.[0-9]+)*">>,[restart_new_emulator]}],%% R15
%% 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
+ [{<<"2\\.0(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R17
+ {<<"1\\.19(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R16
+ {<<"1\\.18(\\.[0-9]+)*">>,[restart_new_emulator]}] %% R15
}.
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..d18387568d 100644
--- a/lib/stdlib/src/supervisor.erl
+++ b/lib/stdlib/src/supervisor.erl
@@ -260,7 +260,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 ->
@@ -752,10 +752,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
@@ -850,7 +856,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),
@@ -1008,7 +1014,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
diff --git a/lib/stdlib/src/sys.erl b/lib/stdlib/src/sys.erl
index c186eab940..04f8dfb61b 100644
--- a/lib/stdlib/src/sys.erl
+++ b/lib/stdlib/src/sys.erl
@@ -317,10 +317,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.
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.