aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r--lib/stdlib/src/array.erl2
-rw-r--r--lib/stdlib/src/c.erl2
-rw-r--r--lib/stdlib/src/dets.erl20
-rw-r--r--lib/stdlib/src/dets_utils.erl4
-rw-r--r--lib/stdlib/src/edlin.erl136
-rw-r--r--lib/stdlib/src/edlin_expand.erl26
-rw-r--r--lib/stdlib/src/erl_lint.erl15
-rw-r--r--lib/stdlib/src/error_logger_file_h.erl36
-rw-r--r--lib/stdlib/src/error_logger_tty_h.erl116
-rw-r--r--lib/stdlib/src/escript.erl2
-rw-r--r--lib/stdlib/src/ets.erl2
-rw-r--r--lib/stdlib/src/gen.erl2
-rw-r--r--lib/stdlib/src/gen_event.erl20
-rw-r--r--lib/stdlib/src/gen_fsm.erl40
-rw-r--r--lib/stdlib/src/gen_server.erl28
-rw-r--r--lib/stdlib/src/gen_statem.erl30
-rw-r--r--lib/stdlib/src/otp_internal.erl18
-rw-r--r--lib/stdlib/src/proc_lib.erl30
-rw-r--r--lib/stdlib/src/qlc.erl2
-rw-r--r--lib/stdlib/src/shell.erl18
-rw-r--r--lib/stdlib/src/slave.erl4
-rw-r--r--lib/stdlib/src/string.erl10
-rw-r--r--lib/stdlib/src/supervisor.erl4
23 files changed, 287 insertions, 280 deletions
diff --git a/lib/stdlib/src/array.erl b/lib/stdlib/src/array.erl
index 079b761463..a237eaa489 100644
--- a/lib/stdlib/src/array.erl
+++ b/lib/stdlib/src/array.erl
@@ -1603,7 +1603,7 @@ foldl_2(I, E, A, Ix, F, D, N, R, S) ->
Ix + S, F, D, N, R, S).
-spec foldl_3(pos_integer(), _, A, array_indx(),
- fun((array_indx, _, A) -> B), integer()) -> B.
+ fun((array_indx(), _, A) -> B), integer()) -> B.
foldl_3(I, E, A, Ix, F, N) when I =< N ->
foldl_3(I+1, E, F(Ix, element(I, E), A), Ix+1, F, N);
diff --git a/lib/stdlib/src/c.erl b/lib/stdlib/src/c.erl
index 4ab9234b81..c04a201ce1 100644
--- a/lib/stdlib/src/c.erl
+++ b/lib/stdlib/src/c.erl
@@ -255,7 +255,7 @@ safe_recompile(File, Options, BeamFile) ->
compile_and_load(File, Opts0) when is_list(Opts0) ->
Opts = [report_errors, report_warnings
| ensure_from(filename:extension(File),
- ensure_outdir(filename:dirname(File), Opts0))],
+ ensure_outdir(".", Opts0))],
case compile:file(File, Opts) of
{ok,Mod} -> %Listing file.
purge_and_load(Mod, File, Opts);
diff --git a/lib/stdlib/src/dets.erl b/lib/stdlib/src/dets.erl
index 10e8c9c800..4e3fe0e5c1 100644
--- a/lib/stdlib/src/dets.erl
+++ b/lib/stdlib/src/dets.erl
@@ -1354,7 +1354,7 @@ open_file_loop2(Head, N) ->
?MODULE, [], Head);
Message ->
error_logger:format("** dets: unexpected message"
- "(ignored): ~w~n", [Message]),
+ "(ignored): ~tw~n", [Message]),
open_file_loop(Head, N)
end.
@@ -1403,7 +1403,7 @@ apply_op(Op, From, Head, N) ->
Head;
_Dirty when N =:= 0 -> % dirty or new_dirty
%% The updates seems to have declined
- dets_utils:vformat("** dets: Auto save of ~p\n",
+ dets_utils:vformat("** dets: Auto save of ~tp\n",
[Head#head.name]),
{NewHead, _Res} = perform_save(Head, true),
erlang:garbage_collect(),
@@ -1587,13 +1587,13 @@ bug_found(Name, Op, Bad, From) ->
%% If stream_op/5 found more requests, this is not
%% the last operation.
error_logger:format
- ("** dets: Bug was found when accessing table ~w,~n"
- "** dets: operation was ~p and reply was ~w.~n"
- "** dets: Stacktrace: ~w~n",
+ ("** dets: Bug was found when accessing table ~tw,~n"
+ "** dets: operation was ~tp and reply was ~tw.~n"
+ "** dets: Stacktrace: ~tw~n",
[Name, Op, Bad, erlang:get_stacktrace()]);
false ->
error_logger:format
- ("** dets: Bug was found when accessing table ~w~n",
+ ("** dets: Bug was found when accessing table ~tw~n",
[Name])
end,
if
@@ -2117,7 +2117,7 @@ do_open_file([Fname, Verbose], Parent, Server, Ref) ->
Error;
Bad ->
error_logger:format
- ("** dets: Bug was found in open_file/1, reply was ~w.~n",
+ ("** dets: Bug was found in open_file/1, reply was ~tw.~n",
[Bad]),
{error, {dets_bug, Fname, Bad}}
end;
@@ -2135,7 +2135,7 @@ do_open_file([Tab, OpenArgs, Verb], Parent, Server, _Ref) ->
Bad ->
error_logger:format
("** dets: Bug was found in open_file/2, arguments were~n"
- "** dets: ~w and reply was ~w.~n",
+ "** dets: ~tw and reply was ~tw.~n",
[OpenArgs, Bad]),
{error, {dets_bug, Tab, {open_file, OpenArgs}, Bad}}
end.
@@ -3123,7 +3123,7 @@ check_safe_fixtable(Head) ->
((get(verbose) =:= yes) orelse dets_utils:debug_mode()) of
true ->
error_logger:format
- ("** dets: traversal of ~p needs safe_fixtable~n",
+ ("** dets: traversal of ~tp needs safe_fixtable~n",
[Head#head.name]);
false ->
ok
@@ -3189,7 +3189,7 @@ scan_read(H, From, _To, Min, _L, Ts, R, C) ->
err(Error) ->
case get(verbose) of
yes ->
- error_logger:format("** dets: failed with ~w~n", [Error]),
+ error_logger:format("** dets: failed with ~tw~n", [Error]),
Error;
undefined ->
Error
diff --git a/lib/stdlib/src/dets_utils.erl b/lib/stdlib/src/dets_utils.erl
index da6ebd18f2..17f55ebdc2 100644
--- a/lib/stdlib/src/dets_utils.erl
+++ b/lib/stdlib/src/dets_utils.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2001-2016. All Rights Reserved.
+%% Copyright Ericsson AB 2001-2017. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -387,7 +387,7 @@ corrupt_reason(Head, Reason0) ->
corrupt(Head, Error) ->
case get(verbose) of
yes ->
- error_logger:format("** dets: Corrupt table ~p: ~tp\n",
+ error_logger:format("** dets: Corrupt table ~tp: ~tp\n",
[Head#head.name, Error]);
_ -> ok
end,
diff --git a/lib/stdlib/src/edlin.erl b/lib/stdlib/src/edlin.erl
index 71e8471c45..5df9c504f9 100644
--- a/lib/stdlib/src/edlin.erl
+++ b/lib/stdlib/src/edlin.erl
@@ -83,7 +83,7 @@ edit_line(Cs, {line,P,L,M}) ->
edit_line1(Cs, {line,P,L,{blink,N}}) ->
edit(Cs, P, L, none, [{move_rel,N}]);
edit_line1(Cs, {line,P,{[],[]},none}) ->
- {more_chars, {line,P,{lists:reverse(Cs),[]},none},[{put_chars, unicode, Cs}]};
+ {more_chars, {line,P,{string:reverse(Cs),[]},none},[{put_chars, unicode, Cs}]};
edit_line1(Cs, {line,P,L,M}) ->
edit(Cs, P, L, M, []).
@@ -93,14 +93,14 @@ edit([C|Cs], P, {Bef,Aft}, Prefix, Rs0) ->
case key_map(C, Prefix) of
meta ->
edit(Cs, P, {Bef,Aft}, meta, Rs0);
- meta_o ->
- edit(Cs, P, {Bef,Aft}, meta_o, Rs0);
- meta_csi ->
- edit(Cs, P, {Bef,Aft}, meta_csi, Rs0);
- meta_meta ->
- edit(Cs, P, {Bef,Aft}, meta_meta, Rs0);
- {csi, _} = Csi ->
- edit(Cs, P, {Bef,Aft}, Csi, Rs0);
+ meta_o ->
+ edit(Cs, P, {Bef,Aft}, meta_o, Rs0);
+ meta_csi ->
+ edit(Cs, P, {Bef,Aft}, meta_csi, Rs0);
+ meta_meta ->
+ edit(Cs, P, {Bef,Aft}, meta_meta, Rs0);
+ {csi, _} = Csi ->
+ edit(Cs, P, {Bef,Aft}, Csi, Rs0);
meta_left_sq_bracket ->
edit(Cs, P, {Bef,Aft}, meta_left_sq_bracket, Rs0);
search_meta ->
@@ -110,8 +110,8 @@ edit([C|Cs], P, {Bef,Aft}, Prefix, Rs0) ->
ctlx ->
edit(Cs, P, {Bef,Aft}, ctlx, Rs0);
new_line ->
- {done, reverse(Bef, Aft ++ "\n"), Cs,
- reverse(Rs0, [{move_rel,length(Aft)},{put_chars,unicode,"\n"}])};
+ {done, get_line(Bef, Aft ++ "\n"), Cs,
+ reverse(Rs0, [{move_rel,cp_len(Aft)},{put_chars,unicode,"\n"}])};
redraw_line ->
Rs1 = erase(P, Bef, Aft, Rs0),
Rs = redraw(P, Bef, Aft, Rs1),
@@ -157,7 +157,7 @@ edit([], P, L, {blink,N}, Rs) ->
edit([], P, L, Prefix, Rs) ->
{more_chars,{line,P,L,Prefix},reverse(Rs)};
edit(eof, _, {Bef,Aft}, _, Rs) ->
- {done,reverse(Bef, Aft),[],reverse(Rs, [{move_rel,length(Aft)}])}.
+ {done,get_line(Bef, Aft),[],reverse(Rs, [{move_rel,cp_len(Aft)}])}.
%% %% Assumes that arg is a string
%% %% Horizontal whitespace only.
@@ -279,11 +279,21 @@ key_map(C, search) -> {insert_search,C};
key_map(C, _) -> {undefined,C}.
%% do_op(Action, Before, After, Requests)
-
-do_op({insert,C}, Bef, [], Rs) ->
- {{[C|Bef],[]},[{put_chars, unicode,[C]}|Rs]};
-do_op({insert,C}, Bef, Aft, Rs) ->
- {{[C|Bef],Aft},[{insert_chars, unicode, [C]}|Rs]};
+%% Before and After are of lists of type string:grapheme_cluster()
+do_op({insert,C}, [], [], Rs) ->
+ {{[C],[]},[{put_chars, unicode,[C]}|Rs]};
+do_op({insert,C}, [Bef|Bef0], [], Rs) ->
+ case string:to_graphemes([Bef,C]) of
+ [GC] -> {{[GC|Bef0],[]},[{put_chars, unicode,[C]}|Rs]};
+ _ -> {{[C,Bef|Bef0],[]},[{put_chars, unicode,[C]}|Rs]}
+ end;
+do_op({insert,C}, [], Aft, Rs) ->
+ {{[C],Aft},[{insert_chars, unicode,[C]}|Rs]};
+do_op({insert,C}, [Bef|Bef0], Aft, Rs) ->
+ case string:to_graphemes([Bef,C]) of
+ [GC] -> {{[GC|Bef0],Aft},[{insert_chars, unicode,[C]}|Rs]};
+ _ -> {{[C,Bef|Bef0],Aft},[{insert_chars, unicode,[C]}|Rs]}
+ end;
%% Search mode prompt always looks like (search)`$TERMS': $RESULT.
%% the {insert_search, _} handlings allow to share this implementation
%% correctly with group.erl. This module provides $TERMS, and group.erl
@@ -299,13 +309,13 @@ do_op({insert_search, C}, Bef, [], Rs) ->
[{insert_chars, unicode, [C]++Aft}, {delete_chars,-3} | Rs],
search};
do_op({insert_search, C}, Bef, Aft, Rs) ->
- Offset= length(Aft),
+ Offset= cp_len(Aft),
NAft = "': ",
{{[C|Bef],NAft},
[{insert_chars, unicode, [C]++NAft}, {delete_chars,-Offset} | Rs],
search};
do_op({search, backward_delete_char}, [_|Bef], Aft, Rs) ->
- Offset= length(Aft)+1,
+ Offset= cp_len(Aft)+1,
NAft = "': ",
{{Bef,NAft},
[{insert_chars, unicode, NAft}, {delete_chars,-Offset}|Rs],
@@ -314,13 +324,13 @@ do_op({search, backward_delete_char}, [], _Aft, Rs) ->
Aft="': ",
{{[],Aft}, Rs, search};
do_op({search, skip_up}, Bef, Aft, Rs) ->
- Offset= length(Aft),
+ Offset= cp_len(Aft),
NAft = "': ",
{{[$\^R|Bef],NAft}, % we insert ^R as a flag to whoever called us
[{insert_chars, unicode, NAft}, {delete_chars,-Offset}|Rs],
search};
do_op({search, skip_down}, Bef, Aft, Rs) ->
- Offset= length(Aft),
+ Offset= cp_len(Aft),
NAft = "': ",
{{[$\^S|Bef],NAft}, % we insert ^S as a flag to whoever called us
[{insert_chars, unicode, NAft}, {delete_chars,-Offset}|Rs],
@@ -328,12 +338,12 @@ do_op({search, skip_down}, Bef, Aft, Rs) ->
do_op({search, search_found}, _Bef, Aft, Rs) ->
"': "++NAft = Aft,
{{[],NAft},
- [{put_chars, unicode, "\n"}, {move_rel,-length(Aft)} | Rs],
+ [{put_chars, unicode, "\n"}, {move_rel,-cp_len(Aft)} | Rs],
search_found};
do_op({search, search_quit}, _Bef, Aft, Rs) ->
"': "++NAft = Aft,
{{[],NAft},
- [{put_chars, unicode, "\n"}, {move_rel,-length(Aft)} | Rs],
+ [{put_chars, unicode, "\n"}, {move_rel,-cp_len(Aft)} | Rs],
search_quit};
%% do blink after $$
do_op({blink,C,M}, Bef=[$$,$$|_], Aft, Rs) ->
@@ -361,14 +371,16 @@ do_op(auto_blink, Bef, Aft, Rs) ->
N -> {blink,N+1,{Bef,Aft},
[{move_rel,-(N+1)}|Rs]}
end;
-do_op(forward_delete_char, Bef, [_|Aft], Rs) ->
- {{Bef,Aft},[{delete_chars,1}|Rs]};
-do_op(backward_delete_char, [_|Bef], Aft, Rs) ->
- {{Bef,Aft},[{delete_chars,-1}|Rs]};
+do_op(forward_delete_char, Bef, [GC|Aft], Rs) ->
+ {{Bef,Aft},[{delete_chars,gc_len(GC)}|Rs]};
+do_op(backward_delete_char, [GC|Bef], Aft, Rs) ->
+ {{Bef,Aft},[{delete_chars,-gc_len(GC)}|Rs]};
do_op(transpose_char, [C1,C2|Bef], [], Rs) ->
- {{[C2,C1|Bef],[]},[{put_chars, unicode,[C1,C2]},{move_rel,-2}|Rs]};
+ Len = gc_len(C1)+gc_len(C2),
+ {{[C2,C1|Bef],[]},[{put_chars, unicode,[C1,C2]},{move_rel,-Len}|Rs]};
do_op(transpose_char, [C2|Bef], [C1|Aft], Rs) ->
- {{[C2,C1|Bef],Aft},[{put_chars, unicode,[C1,C2]},{move_rel,-1}|Rs]};
+ Len = gc_len(C2),
+ {{[C2,C1|Bef],Aft},[{put_chars, unicode,[C1,C2]},{move_rel,-Len}|Rs]};
do_op(kill_word, Bef, Aft0, Rs) ->
{Aft1,Kill0,N0} = over_non_word(Aft0, [], 0),
{Aft,Kill,N} = over_word(Aft1, Kill0, N0),
@@ -381,7 +393,7 @@ do_op(backward_kill_word, Bef0, Aft, Rs) ->
{{Bef,Aft},[{delete_chars,-N}|Rs]};
do_op(kill_line, Bef, Aft, Rs) ->
put(kill_buffer, Aft),
- {{Bef,[]},[{delete_chars,length(Aft)}|Rs]};
+ {{Bef,[]},[{delete_chars,cp_len(Aft)}|Rs]};
do_op(yank, Bef, [], Rs) ->
Kill = get(kill_buffer),
{{reverse(Kill, Bef),[]},[{put_chars, unicode,Kill}|Rs]};
@@ -389,9 +401,9 @@ do_op(yank, Bef, Aft, Rs) ->
Kill = get(kill_buffer),
{{reverse(Kill, Bef),Aft},[{insert_chars, unicode,Kill}|Rs]};
do_op(forward_char, Bef, [C|Aft], Rs) ->
- {{[C|Bef],Aft},[{move_rel,1}|Rs]};
+ {{[C|Bef],Aft},[{move_rel,gc_len(C)}|Rs]};
do_op(backward_char, [C|Bef], Aft, Rs) ->
- {{Bef,[C|Aft]},[{move_rel,-1}|Rs]};
+ {{Bef,[C|Aft]},[{move_rel,-gc_len(C)}|Rs]};
do_op(forward_word, Bef0, Aft0, Rs) ->
{Aft1,Bef1,N0} = over_non_word(Aft0, Bef0, 0),
{Aft,Bef,N} = over_word(Aft1, Bef1, N0),
@@ -400,17 +412,17 @@ do_op(backward_word, Bef0, Aft0, Rs) ->
{Bef1,Aft1,N0} = over_non_word(Bef0, Aft0, 0),
{Bef,Aft,N} = over_word(Bef1, Aft1, N0),
{{Bef,Aft},[{move_rel,-N}|Rs]};
-do_op(beginning_of_line, [C|Bef], Aft, Rs) ->
- {{[],reverse(Bef, [C|Aft])},[{move_rel,-(length(Bef)+1)}|Rs]};
+do_op(beginning_of_line, [_|_]=Bef, Aft, Rs) ->
+ {{[],reverse(Bef, Aft)},[{move_rel,-(cp_len(Bef))}|Rs]};
do_op(beginning_of_line, [], Aft, Rs) ->
{{[],Aft},Rs};
-do_op(end_of_line, Bef, [C|Aft], Rs) ->
- {{reverse(Aft, [C|Bef]),[]},[{move_rel,length(Aft)+1}|Rs]};
+do_op(end_of_line, Bef, [_|_]=Aft, Rs) ->
+ {{reverse(Aft, Bef),[]},[{move_rel,cp_len(Aft)}|Rs]};
do_op(end_of_line, Bef, [], Rs) ->
{{Bef,[]},Rs};
do_op(ctlu, Bef, Aft, Rs) ->
put(kill_buffer, reverse(Bef)),
- {{[], Aft}, [{delete_chars, -length(Bef)} | Rs]};
+ {{[], Aft}, [{delete_chars, -cp_len(Bef)} | Rs]};
do_op(beep, Bef, Aft, Rs) ->
{{Bef,Aft},[beep|Rs]};
do_op(_, Bef, Aft, Rs) ->
@@ -436,7 +448,7 @@ over_word(Cs, Stack, N) ->
until_quote([$\'|Cs], Stack, N) ->
{Cs, [$\'|Stack], N+1};
until_quote([C|Cs], Stack, N) ->
- until_quote(Cs, [C|Stack], N+1).
+ until_quote(Cs, [C|Stack], N+gc_len(C)).
over_word1([$\'=C|Cs], Stack, N) ->
until_quote(Cs, [C|Stack], N+1);
@@ -445,7 +457,7 @@ over_word1(Cs, Stack, N) ->
over_word2([C|Cs], Stack, N) ->
case word_char(C) of
- true -> over_word2(Cs, [C|Stack], N+1);
+ true -> over_word2(Cs, [C|Stack], N+gc_len(C));
false -> {[C|Cs],Stack,N}
end;
over_word2([], Stack, N) when is_integer(N) ->
@@ -454,7 +466,7 @@ over_word2([], Stack, N) when is_integer(N) ->
over_non_word([C|Cs], Stack, N) ->
case word_char(C) of
true -> {[C|Cs],Stack,N};
- false -> over_non_word(Cs, [C|Stack], N+1)
+ false -> over_non_word(Cs, [C|Stack], N+gc_len(C))
end;
over_non_word([], Stack, N) ->
{[],Stack,N}.
@@ -465,6 +477,7 @@ word_char(C) when C >= $a, C =< $z -> true;
word_char(C) when C >= $ß, C =< $ÿ, C =/= $÷ -> true;
word_char(C) when C >= $0, C =< $9 -> true;
word_char(C) when C =:= $_ -> true;
+word_char([_|_]) -> true; %% Is grapheme
word_char(_) -> false.
%% over_white(Chars, InitialStack, InitialCount) ->
@@ -488,8 +501,8 @@ over_paren(Chars, Paren, Match) ->
over_paren([C,$$,$$|Cs], Paren, Match, D, N, L) ->
over_paren([C|Cs], Paren, Match, D, N+2, L);
-over_paren([_,$$|Cs], Paren, Match, D, N, L) ->
- over_paren(Cs, Paren, Match, D, N+2, L);
+over_paren([GC,$$|Cs], Paren, Match, D, N, L) ->
+ over_paren(Cs, Paren, Match, D, N+1+gc_len(GC), L);
over_paren([Match|_], _Paren, Match, 1, N, _) ->
N;
over_paren([Match|Cs], Paren, Match, D, N, [Match|L]) ->
@@ -518,8 +531,8 @@ over_paren([$[|_], _, _, _, _, _) ->
over_paren([${|_], _, _, _, _, _) ->
beep;
-over_paren([_|Cs], Paren, Match, D, N, L) ->
- over_paren(Cs, Paren, Match, D, N+1, L);
+over_paren([GC|Cs], Paren, Match, D, N, L) ->
+ over_paren(Cs, Paren, Match, D, N+gc_len(GC), L);
over_paren([], _, _, _, _, _) ->
0.
@@ -529,8 +542,8 @@ over_paren_auto(Chars) ->
over_paren_auto([C,$$,$$|Cs], D, N, L) ->
over_paren_auto([C|Cs], D, N+2, L);
-over_paren_auto([_,$$|Cs], D, N, L) ->
- over_paren_auto(Cs, D, N+2, L);
+over_paren_auto([GC,$$|Cs], D, N, L) ->
+ over_paren_auto(Cs, D, N+1+gc_len(GC), L);
over_paren_auto([$(|_], _, N, []) ->
{N, $)};
@@ -553,8 +566,8 @@ over_paren_auto([$[|Cs], D, N, [$[|L]) ->
over_paren_auto([${|Cs], D, N, [${|L]) ->
over_paren_auto(Cs, D, N+1, L);
-over_paren_auto([_|Cs], D, N, L) ->
- over_paren_auto(Cs, D, N+1, L);
+over_paren_auto([GC|Cs], D, N, L) ->
+ over_paren_auto(Cs, D, N+gc_len(GC), L);
over_paren_auto([], _, _, _) ->
0.
@@ -574,28 +587,43 @@ erase_inp({line,_,{Bef,Aft},_}) ->
reverse(erase([], Bef, Aft, [])).
erase(Pbs, Bef, Aft, Rs) ->
- [{delete_chars,-length(Pbs)-length(Bef)},{delete_chars,length(Aft)}|Rs].
+ [{delete_chars,-cp_len(Pbs)-cp_len(Bef)},{delete_chars,cp_len(Aft)}|Rs].
redraw_line({line,Pbs,{Bef,Aft},_}) ->
reverse(redraw(Pbs, Bef, Aft, [])).
redraw(Pbs, Bef, Aft, Rs) ->
- [{move_rel,-length(Aft)},{put_chars, unicode,reverse(Bef, Aft)},{put_chars, unicode,Pbs}|Rs].
+ [{move_rel,-cp_len(Aft)},{put_chars, unicode,reverse(Bef, Aft)},{put_chars, unicode,Pbs}|Rs].
length_before({line,Pbs,{Bef,_Aft},_}) ->
- length(Pbs) + length(Bef).
+ cp_len(Pbs) + cp_len(Bef).
length_after({line,_,{_Bef,Aft},_}) ->
- length(Aft).
+ cp_len(Aft).
prompt({line,Pbs,_,_}) ->
Pbs.
current_line({line,_,{Bef, Aft},_}) ->
- reverse(Bef, Aft ++ "\n").
+ get_line(Bef, Aft ++ "\n").
current_chars({line,_,{Bef,Aft},_}) ->
- reverse(Bef, Aft).
+ get_line(Bef, Aft).
+
+get_line(Bef, Aft) ->
+ unicode:characters_to_list(reverse(Bef, Aft)).
+
+%% Grapheme length in codepoints
+gc_len(CP) when is_integer(CP) -> 1;
+gc_len(CPs) when is_list(CPs) -> length(CPs).
+
+%% String length in codepoints
+cp_len(Str) ->
+ cp_len(Str, 0).
+
+cp_len([GC|R], Len) ->
+ cp_len(R, Len + gc_len(GC));
+cp_len([], Len) -> Len.
%% %% expand(CurrentBefore) ->
%% %% {yes,Expansion} | no
diff --git a/lib/stdlib/src/edlin_expand.erl b/lib/stdlib/src/edlin_expand.erl
index a1a97af4c5..bdcefda6e5 100644
--- a/lib/stdlib/src/edlin_expand.erl
+++ b/lib/stdlib/src/edlin_expand.erl
@@ -23,7 +23,7 @@
-export([expand/1, format_matches/1]).
--import(lists, [reverse/1, nthtail/2, prefix/2]).
+-import(lists, [reverse/1, prefix/2]).
%% expand(CurrentBefore) ->
%% {yes, Expansion, Matches} | {no, Matches}
@@ -75,15 +75,15 @@ to_atom(Str) ->
end.
match(Prefix, Alts, Extra0) ->
- Len = length(Prefix),
+ Len = string:length(Prefix),
Matches = lists:sort(
[{S, A} || {H, A} <- Alts,
- prefix(Prefix, S=hd(io_lib:fwrite("~w",[H])))]),
+ prefix(Prefix, S=flat_write(H))]),
case longest_common_head([N || {N, _} <- Matches]) of
{partial, []} ->
{no, [], Matches}; % format_matches(Matches)};
{partial, Str} ->
- case nthtail(Len, Str) of
+ case string:slice(Str, Len) of
[] ->
{yes, [], Matches}; % format_matches(Matches)};
Remain ->
@@ -94,18 +94,21 @@ match(Prefix, Alts, Extra0) ->
{"(",[{Str,0}]} -> "()";
{_,_} -> Extra0
end,
- {yes, nthtail(Len, Str) ++ Extra, []};
+ {yes, string:slice(Str, Len) ++ Extra, []};
no ->
{no, [], []}
end.
+flat_write(T) ->
+ lists:flatten(io_lib:fwrite("~tw",[T])).
+
%% Return the list of names L in multiple columns.
format_matches(L) ->
{S1, Dots} = format_col(lists:sort(L), []),
S = case Dots of
true ->
{_, Prefix} = longest_common_head(vals(L)),
- PrefixLen = length(Prefix),
+ PrefixLen = string:length(Prefix),
case PrefixLen =< 3 of
true -> S1; % Do not replace the prefix with "...".
false ->
@@ -128,7 +131,7 @@ format_col([A|T], Width, Len, Acc0, LL, Dots) ->
{H0, R} = format_val(A),
Hmax = LL - length(R),
{H, NewDots} =
- case length(H0) > Hmax of
+ case string:length(H0) > Hmax of
true -> {io_lib:format("~-*ts", [Hmax - 3, H0]) ++ "...", true};
false -> {H0, Dots}
end,
@@ -149,12 +152,12 @@ format_val(H) ->
field_width(L, LL) -> field_width(L, 0, LL).
field_width([{H,_}|T], W, LL) ->
- case length(H) of
+ case string:length(H) of
L when L > W -> field_width(T, L, LL);
_ -> field_width(T, W, LL)
end;
field_width([H|T], W, LL) ->
- case length(H) of
+ case string:length(H) of
L when L > W -> field_width(T, L, LL);
_ -> field_width(T, W, LL)
end;
@@ -169,10 +172,11 @@ vals([S|L]) -> [S|vals(L)].
leading_dots([], _Len) -> [];
leading_dots([{H, I}|L], Len) ->
- [{"..." ++ nthtail(Len, H), I}|leading_dots(L, Len)];
+ [{"..." ++ string:slice(H, Len), I}|leading_dots(L, Len)];
leading_dots([H|L], Len) ->
- ["..." ++ nthtail(Len, H)|leading_dots(L, Len)].
+ ["..." ++ string:slice(H, Len)|leading_dots(L, Len)].
+%% Strings are handled naively, but it should be OK here.
longest_common_head([]) ->
no;
longest_common_head(LL) ->
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index fcfd0d8493..9cd4727dc3 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -194,8 +194,6 @@ format_error({bad_nowarn_bif_clash,{F,A}}) ->
format_error(disallowed_nowarn_bif_clash) ->
io_lib:format("compile directive nowarn_bif_clash is no longer allowed,~n"
" - use explicit module names or -compile({no_auto_import, [F/A]})", []);
-format_error({bad_nowarn_deprecated_function,{M,F,A}}) ->
- io_lib:format("~tw:~tw/~w is not a deprecated function", [M,F,A]);
format_error({bad_on_load,Term}) ->
io_lib:format("badly formed on_load attribute: ~tw", [Term]);
format_error(multiple_on_loads) ->
@@ -856,14 +854,11 @@ not_deprecated(Forms, St0) ->
{nowarn_deprecated_function, MFAs0} <- lists:flatten([Args]),
MFA <- lists:flatten([MFAs0])],
Nowarn = [MFA || {MFA,_L} <- MFAsL],
- Bad = [MFAL || {{M,F,A},_L}=MFAL <- MFAsL,
- otp_internal:obsolete(M, F, A) =:= no],
- St1 = func_line_warning(bad_nowarn_deprecated_function, Bad, St0),
ML = [{M,L} || {{M,_F,_A},L} <- MFAsL, is_atom(M)],
- St3 = foldl(fun ({M,L}, St2) ->
+ St1 = foldl(fun ({M,L}, St2) ->
check_module_name(M, L, St2)
- end, St1, ML),
- St3#lint{not_deprecated = ordsets:from_list(Nowarn)}.
+ end, St0, ML),
+ St1#lint{not_deprecated = ordsets:from_list(Nowarn)}.
%% The nowarn_bif_clash directive is not only deprecated, it's actually an error from R14A
disallowed_compile_flags(Forms, St0) ->
@@ -3243,13 +3238,13 @@ icrt_clauses(Cs, In, Vt, St0) ->
icrt_clauses(Cs, Vt, St) ->
mapfoldl(fun (C, St0) -> icrt_clause(C, Vt, St0) end, St, Cs).
-icrt_clause({clause,_Line,H,G,B}, Vt0, St0) ->
+icrt_clause({clause,_Line,H,G,B}, Vt0, #lint{catch_scope=Scope}=St0) ->
{Hvt,Binvt,St1} = head(H, Vt0, St0),
Vt1 = vtupdate(Hvt, Binvt),
{Gvt,St2} = guard(G, vtupdate(Vt1, Vt0), St1),
Vt2 = vtupdate(Gvt, Vt1),
{Bvt,St3} = exprs(B, vtupdate(Vt2, Vt0), St2),
- {vtupdate(Bvt, Vt2),St3}.
+ {vtupdate(Bvt, Vt2),St3#lint{catch_scope=Scope}}.
icrt_export(Vts, Vt, {Tag,Attrs}, St) ->
{_File,Loc} = loc(Attrs, St),
diff --git a/lib/stdlib/src/error_logger_file_h.erl b/lib/stdlib/src/error_logger_file_h.erl
index b7c193f965..58da0cbdd6 100644
--- a/lib/stdlib/src/error_logger_file_h.erl
+++ b/lib/stdlib/src/error_logger_file_h.erl
@@ -126,7 +126,7 @@ format_body(State, [{Format,Args}|T]) ->
S0
catch
_:_ ->
- format(State, "ERROR: ~p - ~p\n", [Format,Args])
+ format(State, "ERROR: ~tp - ~tp\n", [Format,Args])
end,
[S|format_body(State, T)];
format_body(_State, []) ->
@@ -165,44 +165,26 @@ parse_event({warning_report, _GL, {Pid, std_warning, Args}}) ->
parse_event(_) -> ignore.
format_term(Term) when is_list(Term) ->
- case string_p(Term) of
+ case string_p(lists:flatten(Term)) of
true ->
- [{"~s\n",[Term]}];
+ [{"~ts\n",[Term]}];
false ->
format_term_list(Term)
end;
format_term(Term) ->
- [{"~p\n",[Term]}].
+ [{"~tp\n",[Term]}].
format_term_list([{Tag,Data}|T]) ->
- [{" ~p: ~p\n",[Tag,Data]}|format_term_list(T)];
+ [{" ~tp: ~tp\n",[Tag,Data]}|format_term_list(T)];
format_term_list([Data|T]) ->
- [{" ~p\n",[Data]}|format_term_list(T)];
+ [{" ~tp\n",[Data]}|format_term_list(T)];
format_term_list([]) ->
- [];
-format_term_list(_) ->
- %% Continue to allow non-proper lists for now.
- %% FIXME: Remove this clause in OTP 19.
[].
string_p([]) ->
false;
-string_p(Term) ->
- string_p1(Term).
-
-string_p1([H|T]) when is_integer(H), H >= $\s, H < 255 ->
- string_p1(T);
-string_p1([$\n|T]) -> string_p1(T);
-string_p1([$\r|T]) -> string_p1(T);
-string_p1([$\t|T]) -> string_p1(T);
-string_p1([$\v|T]) -> string_p1(T);
-string_p1([$\b|T]) -> string_p1(T);
-string_p1([$\f|T]) -> string_p1(T);
-string_p1([$\e|T]) -> string_p1(T);
-string_p1([H|T]) when is_list(H) ->
- string_p1(H) andalso string_p1(T);
-string_p1([]) -> true;
-string_p1(_) -> false.
+string_p(FlatList) ->
+ io_lib:printable_list(FlatList).
get_utc_config() ->
%% SASL utc_log configuration overrides stdlib config
@@ -225,7 +207,7 @@ header(Time, Title) ->
end.
header({{Y,Mo,D},{H,Mi,S}}, Title, UTC) ->
- io_lib:format("~n=~s==== ~p-~s-~p::~s:~s:~s ~s===~n",
+ io_lib:format("~n=~ts==== ~p-~s-~p::~s:~s:~s ~s===~n",
[Title,D,month(Mo),Y,t(H),t(Mi),t(S),UTC]).
t(X) when is_integer(X) ->
diff --git a/lib/stdlib/src/error_logger_tty_h.erl b/lib/stdlib/src/error_logger_tty_h.erl
index 8f0d7b0362..fa940b7264 100644
--- a/lib/stdlib/src/error_logger_tty_h.erl
+++ b/lib/stdlib/src/error_logger_tty_h.erl
@@ -39,13 +39,16 @@
{user,
prev_handler,
io_mod=io,
- depth=unlimited}).
+ depth=unlimited,
+ modifier=""}).
%% This one is used when we takeover from the simple error_logger.
init({[], {error_logger, Buf}}) ->
User = set_group_leader(),
Depth = error_logger:get_format_depth(),
- State = #st{user=User,prev_handler=error_logger,depth=Depth},
+ Modifier = modifier(),
+ State = #st{user=User,prev_handler=error_logger,
+ depth=Depth,modifier=Modifier},
write_events(State, Buf),
{ok, State};
%% This one is used if someone took over from us, and now wants to
@@ -57,7 +60,8 @@ init({[], {error_logger_tty_h, PrevHandler}}) ->
init([]) ->
User = set_group_leader(),
Depth = error_logger:get_format_depth(),
- {ok, #st{user=User,prev_handler=[],depth=Depth}}.
+ Modifier = modifier(),
+ {ok, #st{user=User,prev_handler=[],depth=Depth,modifier=Modifier}}.
handle_event({_Type, GL, _Msg}, State) when node(GL) =/= node() ->
{ok, State};
@@ -91,8 +95,9 @@ code_change(_OldVsn, State, _Extra) ->
write_event(Event, IoMod) ->
do_write_event(#st{io_mod=IoMod}, Event).
-write_event(Event, IoMod, Depth) ->
- do_write_event(#st{io_mod=IoMod,depth=Depth}, Event).
+write_event(Event, IoMod, {Depth, Enc}) ->
+ Modifier = modifier(Enc),
+ do_write_event(#st{io_mod=IoMod,depth=Depth,modifier=Modifier}, Event).
%%% ------------------------------------------------------
@@ -120,12 +125,12 @@ write_events(State, [Ev|Es]) ->
write_events(_State, []) ->
ok.
-do_write_event(State, {Time, Event}) ->
- case parse_event(Event) of
+do_write_event(#st{modifier=M}=State, {Time, Event}) ->
+ case parse_event(Event,M) of
ignore ->
ok;
{Title,Pid,FormatList} ->
- Header = header(Time, Title),
+ Header = header(Time, Title, M),
Body = format_body(State, FormatList),
AtNode = if
node(Pid) =/= node() ->
@@ -144,13 +149,13 @@ do_write_event(State, {Time, Event}) ->
do_write_event(_, _) ->
ok.
-format_body(State, [{Format,Args}|T]) ->
+format_body(#st{modifier=M}=State, [{Format,Args}|T]) ->
S = try format(State, Format, Args) of
S0 ->
S0
catch
_:_ ->
- format(State, "ERROR: ~p - ~p\n", [Format,Args])
+ format(State, "ERROR: ~"++M++"p - ~"++M++"p\n", [Format,Args])
end,
[S|format_body(State, T)];
format_body(_State, []) ->
@@ -174,62 +179,41 @@ limit_format([H|T], Depth) ->
limit_format([], _) ->
[].
-parse_event({error, _GL, {Pid, Format, Args}}) ->
+parse_event({error, _GL, {Pid, Format, Args}},_) ->
{"ERROR REPORT",Pid,[{Format,Args}]};
-parse_event({info_msg, _GL, {Pid, Format, Args}}) ->
+parse_event({info_msg, _GL, {Pid, Format, Args}},_) ->
{"INFO REPORT",Pid,[{Format, Args}]};
-parse_event({warning_msg, _GL, {Pid, Format, Args}}) ->
+parse_event({warning_msg, _GL, {Pid, Format, Args}},_) ->
{"WARNING REPORT",Pid,[{Format,Args}]};
-parse_event({error_report, _GL, {Pid, std_error, Args}}) ->
- {"ERROR REPORT",Pid,format_term(Args)};
-parse_event({info_report, _GL, {Pid, std_info, Args}}) ->
- {"INFO REPORT",Pid,format_term(Args)};
-parse_event({warning_report, _GL, {Pid, std_warning, Args}}) ->
- {"WARNING REPORT",Pid,format_term(Args)};
-parse_event(_) -> ignore.
-
-format_term(Term) when is_list(Term) ->
- case string_p(Term) of
+parse_event({error_report, _GL, {Pid, std_error, Args}},M) ->
+ {"ERROR REPORT",Pid,format_term(Args,M)};
+parse_event({info_report, _GL, {Pid, std_info, Args}},M) ->
+ {"INFO REPORT",Pid,format_term(Args,M)};
+parse_event({warning_report, _GL, {Pid, std_warning, Args}},M) ->
+ {"WARNING REPORT",Pid,format_term(Args,M)};
+parse_event(_,_) -> ignore.
+
+format_term(Term,M) when is_list(Term) ->
+ case string_p(lists:flatten(Term)) of
true ->
- [{"~s\n",[Term]}];
+ [{"~"++M++"s\n",[Term]}];
false ->
- format_term_list(Term)
+ format_term_list(Term,M)
end;
-format_term(Term) ->
- [{"~p\n",[Term]}].
-
-format_term_list([{Tag,Data}|T]) ->
- [{" ~p: ~p\n",[Tag,Data]}|format_term_list(T)];
-format_term_list([Data|T]) ->
- [{" ~p\n",[Data]}|format_term_list(T)];
-format_term_list([]) ->
- [];
-format_term_list(_) ->
- %% Continue to allow non-proper lists for now.
- %% FIXME: Remove this clause in OTP 19.
+format_term(Term,M) ->
+ [{"~"++M++"p\n",[Term]}].
+
+format_term_list([{Tag,Data}|T],M) ->
+ [{" ~"++M++"p: ~"++M++"p\n",[Tag,Data]}|format_term_list(T,M)];
+format_term_list([Data|T],M) ->
+ [{" ~"++M++"p\n",[Data]}|format_term_list(T,M)];
+format_term_list([],_) ->
[].
string_p([]) ->
false;
-string_p(Term) ->
- string_p1(Term).
-
-string_p1([H|T]) when is_integer(H), H >= $\s, H < 255 ->
- string_p1(T);
-string_p1([$\n|T]) -> string_p1(T);
-string_p1([$\r|T]) -> string_p1(T);
-string_p1([$\t|T]) -> string_p1(T);
-string_p1([$\v|T]) -> string_p1(T);
-string_p1([$\b|T]) -> string_p1(T);
-string_p1([$\f|T]) -> string_p1(T);
-string_p1([$\e|T]) -> string_p1(T);
-string_p1([H|T]) when is_list(H) ->
- case string_p1(H) of
- true -> string_p1(T);
- _ -> false
- end;
-string_p1([]) -> true;
-string_p1(_) -> false.
+string_p(FlatList) ->
+ io_lib:printable_list(FlatList).
get_utc_config() ->
%% SASL utc_log configuration overrides stdlib config
@@ -243,16 +227,16 @@ get_utc_config() ->
end
end.
-header(Time, Title) ->
+header(Time, Title, M) ->
case get_utc_config() of
true ->
- header(Time, Title, "UTC ");
+ header(Time, Title, "UTC ", M);
_ ->
- header(calendar:universal_time_to_local_time(Time), Title, "")
+ header(calendar:universal_time_to_local_time(Time), Title, "", M)
end.
-header({{Y,Mo,D},{H,Mi,S}}, Title, UTC) ->
- io_lib:format("~n=~s==== ~p-~s-~p::~s:~s:~s ~s===~n",
+header({{Y,Mo,D},{H,Mi,S}}, Title, UTC, M) ->
+ io_lib:format("~n=~"++M++"s==== ~p-~s-~p::~s:~s:~s ~s===~n",
[Title,D,month(Mo),Y,t(H),t(Mi),t(S),UTC]).
t(X) when is_integer(X) ->
@@ -274,3 +258,13 @@ month(9) -> "Sep";
month(10) -> "Oct";
month(11) -> "Nov";
month(12) -> "Dec".
+
+modifier() ->
+ modifier(encoding()).
+modifier(latin1) ->
+ "";
+modifier(_) ->
+ "t".
+
+encoding() ->
+ proplists:get_value(encoding,io:getopts(),latin1).
diff --git a/lib/stdlib/src/escript.erl b/lib/stdlib/src/escript.erl
index 2093916a7c..2b9d8ff65b 100644
--- a/lib/stdlib/src/escript.erl
+++ b/lib/stdlib/src/escript.erl
@@ -860,7 +860,7 @@ code_handler(Name, Args, Dict, File) ->
%% io:format("Calling:~p~n",[{Mod,Name,Args}]),
apply(Mod, Name, Args);
error ->
- io:format("Script does not export ~w/~w\n", [Name,Arity]),
+ io:format("Script does not export ~tw/~w\n", [Name,Arity]),
my_halt(127)
end
end.
diff --git a/lib/stdlib/src/ets.erl b/lib/stdlib/src/ets.erl
index 898b2f5bba..b5d3cd3c8d 100644
--- a/lib/stdlib/src/ets.erl
+++ b/lib/stdlib/src/ets.erl
@@ -1693,7 +1693,7 @@ choice(Height, Width, P, Mode, Tab, Key, Turn, Opos) ->
end,
choice(Height, Width, P, Mode, Tab, Key, Turn, Opos);
[$/|Regexp] -> %% from regexp
- case re:compile(nonl(Regexp)) of
+ case re:compile(nonl(Regexp),[unicode]) of
{ok,Re} ->
re_search(Height, Width, Tab, ets:first(Tab), Re, 1, 1);
{error,{ErrorString,_Pos}} ->
diff --git a/lib/stdlib/src/gen.erl b/lib/stdlib/src/gen.erl
index 32f43fc706..33af0aed8f 100644
--- a/lib/stdlib/src/gen.erl
+++ b/lib/stdlib/src/gen.erl
@@ -422,7 +422,7 @@ debug_options(Name, Opts) ->
try sys:debug_options(Options)
catch _:_ ->
error_logger:format(
- "~p: ignoring erroneous debug options - ~p~n",
+ "~tp: ignoring erroneous debug options - ~tp~n",
[Name,Options]),
[]
end;
diff --git a/lib/stdlib/src/gen_event.erl b/lib/stdlib/src/gen_event.erl
index da2b0da3ca..a9b98911e2 100644
--- a/lib/stdlib/src/gen_event.erl
+++ b/lib/stdlib/src/gen_event.erl
@@ -441,15 +441,15 @@ system_replace_state(StateFun, [ServerName, MSL, HibernateAfterTimeout, Hib]) ->
print_event(Dev, {in, Msg}, Name) ->
case Msg of
{notify, Event} ->
- io:format(Dev, "*DBG* ~p got event ~p~n", [Name, Event]);
+ io:format(Dev, "*DBG* ~tp got event ~tp~n", [Name, Event]);
{_,_,{call, Handler, Query}} ->
- io:format(Dev, "*DBG* ~p(~p) got call ~p~n",
+ io:format(Dev, "*DBG* ~tp(~tp) got call ~tp~n",
[Name, Handler, Query]);
_ ->
- io:format(Dev, "*DBG* ~p got ~p~n", [Name, Msg])
+ io:format(Dev, "*DBG* ~tp got ~tp~n", [Name, Msg])
end;
print_event(Dev, Dbg, Name) ->
- io:format(Dev, "*DBG* ~p : ~p~n", [Name, Dbg]).
+ io:format(Dev, "*DBG* ~tp : ~tp~n", [Name, Dbg]).
%% server_add_handler(Handler, Args, MSL) -> {Ret, MSL'}.
@@ -582,8 +582,8 @@ server_update(Handler1, Func, Event, SName) ->
remove, SName, normal),
no;
{'EXIT', {undef, [{Mod1, handle_info, [_,_], _}|_]}} ->
- error_logger:warning_msg("** Undefined handle_info in ~p~n"
- "** Unhandled message: ~p~n", [Mod1, Event]),
+ error_logger:warning_msg("** Undefined handle_info in ~tp~n"
+ "** Unhandled message: ~tp~n", [Mod1, Event]),
{ok, Handler1};
Other ->
do_terminate(Mod1, Handler1, {error, Other}, State,
@@ -767,10 +767,10 @@ report_error(Handler, Reason, State, LastIn, SName) ->
State
end,
error_msg("** gen_event handler ~p crashed.~n"
- "** Was installed in ~p~n"
- "** Last event was: ~p~n"
- "** When handler state == ~p~n"
- "** Reason == ~p~n",
+ "** Was installed in ~tp~n"
+ "** Last event was: ~tp~n"
+ "** When handler state == ~tp~n"
+ "** Reason == ~tp~n",
[handler(Handler),SName,LastIn,FmtState,Reason1]).
handler(Handler) when not Handler#handler.id ->
diff --git a/lib/stdlib/src/gen_fsm.erl b/lib/stdlib/src/gen_fsm.erl
index 9ef0ca818c..96a53426e2 100644
--- a/lib/stdlib/src/gen_fsm.erl
+++ b/lib/stdlib/src/gen_fsm.erl
@@ -452,30 +452,30 @@ system_replace_state(StateFun, [Name, StateName, StateData, Mod, Time, Hibernate
print_event(Dev, {in, Msg}, {Name, StateName}) ->
case Msg of
{'$gen_event', Event} ->
- io:format(Dev, "*DBG* ~p got event ~p in state ~w~n",
+ io:format(Dev, "*DBG* ~tp got event ~tp in state ~tw~n",
[Name, Event, StateName]);
{'$gen_all_state_event', Event} ->
io:format(Dev,
- "*DBG* ~p got all_state_event ~p in state ~w~n",
+ "*DBG* ~tp got all_state_event ~tp in state ~tw~n",
[Name, Event, StateName]);
{timeout, Ref, {'$gen_timer', Message}} ->
io:format(Dev,
- "*DBG* ~p got timer ~p in state ~w~n",
+ "*DBG* ~tp got timer ~tp in state ~tw~n",
[Name, {timeout, Ref, Message}, StateName]);
{timeout, _Ref, {'$gen_event', Event}} ->
io:format(Dev,
- "*DBG* ~p got timer ~p in state ~w~n",
+ "*DBG* ~tp got timer ~tp in state ~tw~n",
[Name, Event, StateName]);
_ ->
- io:format(Dev, "*DBG* ~p got ~p in state ~w~n",
+ io:format(Dev, "*DBG* ~tp got ~tp in state ~tw~n",
[Name, Msg, StateName])
end;
print_event(Dev, {out, Msg, To, StateName}, Name) ->
- io:format(Dev, "*DBG* ~p sent ~p to ~w~n"
- " and switched to state ~w~n",
+ io:format(Dev, "*DBG* ~tp sent ~tp to ~tw~n"
+ " and switched to state ~tw~n",
[Name, Msg, To, StateName]);
print_event(Dev, return, {Name, StateName}) ->
- io:format(Dev, "*DBG* ~p switched to state ~w~n",
+ io:format(Dev, "*DBG* ~tp switched to state ~tw~n",
[Name, StateName]).
handle_msg(Msg, Parent, Name, StateName, StateData, Mod, _Time, HibernateAfterTimeout) -> %No debug here
@@ -500,7 +500,7 @@ handle_msg(Msg, Parent, Name, StateName, StateData, Mod, _Time, HibernateAfterTi
exit(R);
{'EXIT', {undef, [{Mod, handle_info, [_,_,_], _}|_]}} ->
error_logger:warning_msg("** Undefined handle_info in ~p~n"
- "** Unhandled message: ~p~n", [Mod, Msg]),
+ "** Unhandled message: ~tp~n", [Mod, Msg]),
loop(Parent, Name, StateName, StateData, Mod, infinity, HibernateAfterTimeout, []);
{'EXIT', What} ->
terminate(What, Name, Msg, Mod, StateName, StateData, []);
@@ -620,29 +620,29 @@ error_info(Reason, Name, Msg, StateName, StateData, Debug) ->
_ ->
Reason
end,
- Str = "** State machine ~p terminating \n" ++
+ Str = "** State machine ~tp terminating \n" ++
get_msg_str(Msg) ++
- "** When State == ~p~n"
- "** Data == ~p~n"
- "** Reason for termination = ~n** ~p~n",
+ "** When State == ~tp~n"
+ "** Data == ~tp~n"
+ "** Reason for termination = ~n** ~tp~n",
format(Str, [Name, get_msg(Msg), StateName, StateData, Reason1]),
sys:print_log(Debug),
ok.
get_msg_str({'$gen_event', _Event}) ->
- "** Last event in was ~p~n";
+ "** Last event in was ~tp~n";
get_msg_str({'$gen_sync_event', _Event}) ->
- "** Last sync event in was ~p~n";
+ "** Last sync event in was ~tp~n";
get_msg_str({'$gen_all_state_event', _Event}) ->
- "** Last event in was ~p (for all states)~n";
+ "** Last event in was ~tp (for all states)~n";
get_msg_str({'$gen_sync_all_state_event', _Event}) ->
- "** Last sync event in was ~p (for all states)~n";
+ "** Last sync event in was ~tp (for all states)~n";
get_msg_str({timeout, _Ref, {'$gen_timer', _Msg}}) ->
- "** Last timer event in was ~p~n";
+ "** Last timer event in was ~tp~n";
get_msg_str({timeout, _Ref, {'$gen_event', _Msg}}) ->
- "** Last timer event in was ~p~n";
+ "** Last timer event in was ~tp~n";
get_msg_str(_Msg) ->
- "** Last message in was ~p~n".
+ "** Last message in was ~tp~n".
get_msg({'$gen_event', Event}) -> Event;
get_msg({'$gen_sync_event', Event}) -> Event;
diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl
index a3d53efd0d..7daa7a9fe4 100644
--- a/lib/stdlib/src/gen_server.erl
+++ b/lib/stdlib/src/gen_server.erl
@@ -621,7 +621,7 @@ try_dispatch(Mod, Func, Msg, State) ->
case erlang:function_exported(Mod, handle_info, 2) of
false ->
error_logger:warning_msg("** Undefined handle_info in ~p~n"
- "** Unhandled message: ~p~n",
+ "** Unhandled message: ~tp~n",
[Mod, Msg]),
{ok, {noreply, State}};
true ->
@@ -785,21 +785,21 @@ system_replace_state(StateFun, [Name, State, Mod, Time, HibernateAfterTimeout])
print_event(Dev, {in, Msg}, Name) ->
case Msg of
{'$gen_call', {From, _Tag}, Call} ->
- io:format(Dev, "*DBG* ~p got call ~p from ~w~n",
+ io:format(Dev, "*DBG* ~tp got call ~tp from ~w~n",
[Name, Call, From]);
{'$gen_cast', Cast} ->
- io:format(Dev, "*DBG* ~p got cast ~p~n",
+ io:format(Dev, "*DBG* ~tp got cast ~tp~n",
[Name, Cast]);
_ ->
- io:format(Dev, "*DBG* ~p got ~p~n", [Name, Msg])
+ io:format(Dev, "*DBG* ~tp got ~tp~n", [Name, Msg])
end;
print_event(Dev, {out, Msg, To, State}, Name) ->
- io:format(Dev, "*DBG* ~p sent ~p to ~w, new state ~w~n",
+ io:format(Dev, "*DBG* ~tp sent ~tp to ~w, new state ~tp~n",
[Name, Msg, To, State]);
print_event(Dev, {noreply, State}, Name) ->
- io:format(Dev, "*DBG* ~p new state ~w~n", [Name, State]);
+ io:format(Dev, "*DBG* ~tp new state ~tp~n", [Name, State]);
print_event(Dev, Event, Name) ->
- io:format(Dev, "*DBG* ~p dbg ~p~n", [Name, Event]).
+ io:format(Dev, "*DBG* ~tp dbg ~tp~n", [Name, Event]).
%%% ---------------------------------------------------
@@ -881,10 +881,10 @@ error_info(Reason, Name, From, Msg, State, Debug) ->
end,
{ClientFmt, ClientArgs} = client_stacktrace(From),
LimitedState = error_logger:limit_term(State),
- error_logger:format("** Generic server ~p terminating \n"
- "** Last message in was ~p~n"
- "** When Server state == ~p~n"
- "** Reason for termination == ~n** ~p~n" ++ ClientFmt,
+ error_logger:format("** Generic server ~tp terminating \n"
+ "** Last message in was ~tp~n"
+ "** When Server state == ~tp~n"
+ "** Reason for termination == ~n** ~tp~n" ++ ClientFmt,
[Name, Msg, LimitedState, Reason1] ++ ClientArgs),
sys:print_log(Debug),
ok.
@@ -898,11 +898,11 @@ client_stacktrace(From) when is_pid(From), node(From) =:= node() ->
{"** Client ~p is dead~n", [From]};
[{current_stacktrace, Stacktrace}, {registered_name, []}] ->
{"** Client ~p stacktrace~n"
- "** ~p~n",
+ "** ~tp~n",
[From, Stacktrace]};
[{current_stacktrace, Stacktrace}, {registered_name, Name}] ->
- {"** Client ~p stacktrace~n"
- "** ~p~n",
+ {"** Client ~tp stacktrace~n"
+ "** ~tp~n",
[Name, Stacktrace]}
end;
client_stacktrace(From) when is_pid(From) ->
diff --git a/lib/stdlib/src/gen_statem.erl b/lib/stdlib/src/gen_statem.erl
index b5e9da1e66..1110d18af6 100644
--- a/lib/stdlib/src/gen_statem.erl
+++ b/lib/stdlib/src/gen_statem.erl
@@ -791,34 +791,34 @@ format_status(
print_event(Dev, {in,Event}, {Name,State}) ->
io:format(
- Dev, "*DBG* ~p receive ~s in state ~p~n",
+ Dev, "*DBG* ~tp receive ~ts in state ~tp~n",
[Name,event_string(Event),State]);
print_event(Dev, {out,Reply,{To,_Tag}}, {Name,State}) ->
io:format(
- Dev, "*DBG* ~p send ~p to ~p from state ~p~n",
+ Dev, "*DBG* ~tp send ~tp to ~p from state ~tp~n",
[Name,Reply,To,State]);
print_event(Dev, {terminate,Reason}, {Name,State}) ->
io:format(
- Dev, "*DBG* ~p terminate ~p in state ~p~n",
+ Dev, "*DBG* ~tp terminate ~tp in state ~tp~n",
[Name,Reason,State]);
print_event(Dev, {Tag,Event,NextState}, {Name,State}) ->
StateString =
case NextState of
State ->
- io_lib:format("~p", [State]);
+ io_lib:format("~tp", [State]);
_ ->
- io_lib:format("~p => ~p", [State,NextState])
+ io_lib:format("~tp => ~tp", [State,NextState])
end,
io:format(
- Dev, "*DBG* ~p ~w ~s in state ~s~n",
+ Dev, "*DBG* ~tp ~tw ~ts in state ~ts~n",
[Name,Tag,event_string(Event),StateString]).
event_string(Event) ->
case Event of
{{call,{Pid,_Tag}},Request} ->
- io_lib:format("call ~p from ~w", [Request,Pid]);
+ io_lib:format("call ~tp from ~w", [Request,Pid]);
{EventType,EventContent} ->
- io_lib:format("~w ~p", [EventType,EventContent])
+ io_lib:format("~tw ~tp", [EventType,EventContent])
end.
sys_debug(Debug, #{name := Name}, State, Entry) ->
@@ -1732,25 +1732,25 @@ error_info(
CallbackMode
end,
error_logger:format(
- "** State machine ~p terminating~n" ++
+ "** State machine ~tp terminating~n" ++
case Q of
[] -> "";
- _ -> "** Last event = ~p~n"
+ _ -> "** Last event = ~tp~n"
end ++
- "** When server state = ~p~n" ++
- "** Reason for termination = ~w:~p~n" ++
+ "** When server state = ~tp~n" ++
+ "** Reason for termination = ~w:~tp~n" ++
"** Callback mode = ~p~n" ++
case Q of
- [_,_|_] -> "** Queued = ~p~n";
+ [_,_|_] -> "** Queued = ~tp~n";
_ -> ""
end ++
case P of
[] -> "";
- _ -> "** Postponed = ~p~n"
+ _ -> "** Postponed = ~tp~n"
end ++
case FixedStacktrace of
[] -> "";
- _ -> "** Stacktrace =~n** ~p~n"
+ _ -> "** Stacktrace =~n** ~tp~n"
end,
[Name |
case Q of
diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl
index 9e9c0dc413..c59db903dc 100644
--- a/lib/stdlib/src/otp_internal.erl
+++ b/lib/stdlib/src/otp_internal.erl
@@ -63,9 +63,9 @@ obsolete_1(gen_fsm, start, 4) ->
{deprecated, {gen_statem, start, 4}};
obsolete_1(gen_fsm, start_link, 3) ->
- {deprecated, {gen_statem, start, 3}};
+ {deprecated, {gen_statem, start_link, 3}};
obsolete_1(gen_fsm, start_link, 4) ->
- {deprecated, {gen_statem, start, 4}};
+ {deprecated, {gen_statem, start_link, 4}};
obsolete_1(gen_fsm, stop, 1) ->
{deprecated, {gen_statem, stop, 1}};
@@ -83,9 +83,9 @@ obsolete_1(gen_fsm, reply, 2) ->
{deprecated, {gen_statem, reply, 2}};
obsolete_1(gen_fsm, send_event, 2) ->
- {deprecated, {gen_statem, cast, 1}};
+ {deprecated, {gen_statem, cast, 2}};
obsolete_1(gen_fsm, send_all_state_event, 2) ->
- {deprecated, {gen_statem, cast, 1}};
+ {deprecated, {gen_statem, cast, 2}};
obsolete_1(gen_fsm, sync_send_event, 2) ->
{deprecated, {gen_statem, call, 2}};
@@ -98,11 +98,11 @@ obsolete_1(gen_fsm, sync_send_all_state_event, 3) ->
{deprecated, {gen_statem, call, 3}};
obsolete_1(gen_fsm, start_timer, 2) ->
- {deprecated, {erlang, start_timer, 2}};
+ {deprecated, {erlang, start_timer, 3}};
obsolete_1(gen_fsm, cancel_timer, 1) ->
{deprecated, {erlang, cancel_timer, 1}};
obsolete_1(gen_fsm, send_event_after, 2) ->
- {deprecated, {erlang, send_after, 2}};
+ {deprecated, {erlang, send_after, 3}};
%% *** CRYPTO added in OTP 20 ***
@@ -112,7 +112,7 @@ obsolete_1(crypto, rand_uniform, 2) ->
%% *** CRYPTO added in OTP 19 ***
obsolete_1(crypto, rand_bytes, 1) ->
- {deprecated, {crypto, strong_rand_bytes, 1}};
+ {removed, {crypto, strong_rand_bytes, 1}, "20.0"};
%% *** CRYPTO added in R16B01 ***
@@ -485,10 +485,6 @@ obsolete_1(wxPaintDC, new, 0) ->
{deprecated,"deprecated function not available in wxWidgets-2.9 and later"};
obsolete_1(wxWindowDC, new, 0) ->
{deprecated,"deprecated function not available in wxWidgets-2.9 and later"};
-obsolete_1(wxGraphicsContext, createLinearGradientBrush, 7) ->
- {deprecated,"deprecated function not available in wxWidgets-2.9 and later"};
-obsolete_1(wxGraphicsContext, createRadialGradientBrush, 8) ->
- {deprecated,"deprecated function not available in wxWidgets-2.9 and later"};
obsolete_1(wxGraphicsRenderer, createLinearGradientBrush, 7) ->
{deprecated,"deprecated function not available in wxWidgets-2.9 and later"};
obsolete_1(wxGraphicsRenderer, createRadialGradientBrush, 8) ->
diff --git a/lib/stdlib/src/proc_lib.erl b/lib/stdlib/src/proc_lib.erl
index 9ce8e7d60e..8e10cbe93b 100644
--- a/lib/stdlib/src/proc_lib.erl
+++ b/lib/stdlib/src/proc_lib.erl
@@ -779,11 +779,13 @@ format_link_report([Link|Reps], Indent, Extra) ->
LinkIndent = [" ",Indent],
[Indent,"neighbour:\n",format_report(Rep, LinkIndent, Extra)|
format_link_report(Reps, Indent, Extra)];
-format_link_report([], _, _) ->
- [].
+format_link_report(Rep, Indent, Extra) ->
+ format_report(Rep, Indent, Extra).
format_report(Rep, Indent, Extra) when is_list(Rep) ->
format_rep(Rep, Indent, Extra);
+format_report(Rep, Indent, {Enc,unlimited}) ->
+ io_lib:format("~s~"++modifier(Enc)++"p~n", [Indent, Rep]);
format_report(Rep, Indent, {Enc,Depth}) ->
io_lib:format("~s~"++modifier(Enc)++"P~n", [Indent, Rep, Depth]).
@@ -821,22 +823,22 @@ to_string(A, _) ->
io_lib:write_atom(A).
pp_fun({Enc,Depth}) ->
- {Letter,Tl} = case Depth of
- unlimited -> {"p",[]};
- _ -> {"P",[Depth]}
- end,
- P = modifier(Enc) ++ Letter,
+ {P,Tl} = p(Enc, Depth),
fun(Term, I) ->
io_lib:format("~." ++ integer_to_list(I) ++ P, [Term|Tl])
end.
-format_tag(Indent, Tag, Data, {_Enc,Depth}) ->
- case Depth of
- unlimited ->
- io_lib:format("~s~p: ~80.18p~n", [Indent, Tag, Data]);
- _ ->
- io_lib:format("~s~p: ~80.18P~n", [Indent, Tag, Data, Depth])
- end.
+format_tag(Indent, Tag, Data, {Enc,Depth}) ->
+ {P,Tl} = p(Enc, Depth),
+ io_lib:format("~s~p: ~80.18" ++ P ++ "\n", [Indent, Tag, Data|Tl]).
+
+p(Encoding, Depth) ->
+ {Letter, Tl} = case Depth of
+ unlimited -> {"p", []};
+ _ -> {"P", [Depth]}
+ end,
+ P = modifier(Encoding) ++ Letter,
+ {P, Tl}.
modifier(latin1) -> "";
modifier(_) -> "t".
diff --git a/lib/stdlib/src/qlc.erl b/lib/stdlib/src/qlc.erl
index 535ca57a6b..f11f9d0a0b 100644
--- a/lib/stdlib/src/qlc.erl
+++ b/lib/stdlib/src/qlc.erl
@@ -1132,7 +1132,7 @@ wait_for_request(Parent, MonRef, Post) ->
wait_for_request(Parent, MonRef, Post);
Other ->
error_logger:error_msg(
- "The qlc cursor ~w received an unexpected message:\n~p\n",
+ "The qlc cursor ~w received an unexpected message:\n~tp\n",
[self(), Other]),
wait_for_request(Parent, MonRef, Post)
end.
diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl
index 6eafc7b209..212b143b1d 100644
--- a/lib/stdlib/src/shell.erl
+++ b/lib/stdlib/src/shell.erl
@@ -727,7 +727,7 @@ result_will_be_saved() ->
used_record_defs(E, RT) ->
%% Be careful to return a list where used records come before
%% records that use them. The linter wants them ordered that way.
- UR = case used_records(E, [], RT) of
+ UR = case used_records(E, [], RT, []) of
[] ->
[];
L0 ->
@@ -737,13 +737,19 @@ used_record_defs(E, RT) ->
end,
record_defs(RT, UR).
-used_records(E, U0, RT) ->
+used_records(E, U0, RT, Skip) ->
case used_records(E) of
{name,Name,E1} ->
- U = used_records(ets:lookup(RT, Name), [Name | U0], RT),
- used_records(E1, U, RT);
+ U = case lists:member(Name, Skip) of
+ true ->
+ U0;
+ false ->
+ R = ets:lookup(RT, Name),
+ used_records(R, [Name | U0], RT, [Name | Skip])
+ end,
+ used_records(E1, U, RT, Skip);
{expr,[E1 | Es]} ->
- used_records(Es, used_records(E1, U0, RT), RT);
+ used_records(Es, used_records(E1, U0, RT, Skip), RT, Skip);
_ ->
U0
end.
@@ -1453,7 +1459,7 @@ check_env(V) ->
{ok, Val} ->
Txt = io_lib:fwrite
("Invalid value of STDLIB configuration parameter"
- "~w: ~tp\n", [V, Val]),
+ "~tw: ~tp\n", [V, Val]),
error_logger:info_report(lists:flatten(Txt))
end.
diff --git a/lib/stdlib/src/slave.erl b/lib/stdlib/src/slave.erl
index 5b5c328c0c..d7cf6386f5 100644
--- a/lib/stdlib/src/slave.erl
+++ b/lib/stdlib/src/slave.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2016. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2017. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -77,7 +77,7 @@ start_pseudo(_,_,_) -> ok. %% It's already there
Pid :: pid().
relay({badrpc,Reason}) ->
- error_msg(" ** exiting relay server ~w :~w **~n", [self(),Reason]),
+ error_msg(" ** exiting relay server ~w :~tw **~n", [self(),Reason]),
exit(Reason);
relay(undefined) ->
error_msg(" ** exiting relay server ~w **~n", [self()]),
diff --git a/lib/stdlib/src/string.erl b/lib/stdlib/src/string.erl
index 6f7009b5d9..4972da297d 100644
--- a/lib/stdlib/src/string.erl
+++ b/lib/stdlib/src/string.erl
@@ -384,7 +384,7 @@ to_float(String) ->
end.
to_number(String, Number, Rest, List, _Tail) when is_binary(String) ->
- BSz = length(List)-length(Rest),
+ BSz = erlang:length(List)-erlang:length(Rest),
<<_:BSz/binary, Cont/binary>> = String,
{Number, Cont};
to_number(_, Number, Rest, _, Tail) ->
@@ -1344,7 +1344,7 @@ bin_search_str(Bin0, Start, Cont, [CP|_]=SearchCPs) ->
String :: string(),
Length :: non_neg_integer().
-len(S) -> length(S).
+len(S) -> erlang:length(S).
%% equal(String1, String2)
%% Test if 2 strings are equal.
@@ -1689,7 +1689,7 @@ left(String, Len) when is_integer(Len) -> left(String, Len, $\s).
Character :: char().
left(String, Len, Char) when is_integer(Char) ->
- Slen = length(String),
+ Slen = erlang:length(String),
if
Slen > Len -> substr(String, 1, Len);
Slen < Len -> l_pad(String, Len-Slen, Char);
@@ -1714,7 +1714,7 @@ right(String, Len) when is_integer(Len) -> right(String, Len, $\s).
Character :: char().
right(String, Len, Char) when is_integer(Char) ->
- Slen = length(String),
+ Slen = erlang:length(String),
if
Slen > Len -> substr(String, Slen-Len+1);
Slen < Len -> r_pad(String, Len-Slen, Char);
@@ -1741,7 +1741,7 @@ centre(String, Len) when is_integer(Len) -> centre(String, Len, $\s).
centre(String, 0, Char) when is_list(String), is_integer(Char) ->
[]; % Strange cases to centre string
centre(String, Len, Char) when is_integer(Char) ->
- Slen = length(String),
+ Slen = erlang:length(String),
if
Slen > Len -> substr(String, (Slen-Len) div 2 + 1, Len);
Slen < Len ->
diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl
index 1cd65fbf18..7920e55930 100644
--- a/lib/stdlib/src/supervisor.erl
+++ b/lib/stdlib/src/supervisor.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2016. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2017. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -628,7 +628,7 @@ handle_info({'EXIT', Pid, Reason}, State) ->
end;
handle_info(Msg, State) ->
- error_logger:error_msg("Supervisor received unexpected message: ~p~n",
+ error_logger:error_msg("Supervisor received unexpected message: ~tp~n",
[Msg]),
{noreply, State}.