diff options
Diffstat (limited to 'lib/stdlib/src/io_lib.erl')
-rw-r--r-- | lib/stdlib/src/io_lib.erl | 247 |
1 files changed, 176 insertions, 71 deletions
diff --git a/lib/stdlib/src/io_lib.erl b/lib/stdlib/src/io_lib.erl index 50bf959db5..8223a52873 100644 --- a/lib/stdlib/src/io_lib.erl +++ b/lib/stdlib/src/io_lib.erl @@ -60,11 +60,12 @@ -module(io_lib). --export([fwrite/2,fread/2,fread/3,format/2]). --export([scan_format/2,unscan_format/1,build_text/1]). +-export([fwrite/2,fwrite/3,fread/2,fread/3,format/2,format/3]). +-export([scan_format/2,unscan_format/1,build_text/1,build_text/2]). -export([print/1,print/4,indentation/2]). -export([write/1,write/2,write/3,nl/0,format_prompt/1,format_prompt/2]). +-export([write_binary/3]). -export([write_atom/1,write_string/1,write_string/2,write_latin1_string/1, write_latin1_string/2, write_char/1, write_latin1_char/1]). @@ -87,7 +88,7 @@ -export([limit_term/2]). -export_type([chars/0, latin1_string/0, continuation/0, - fread_error/0, fread_item/0, format_spec/0]). + fread_error/0, fread_item/0, format_spec/0, chars_limit/0]). %%---------------------------------------------------------------------- @@ -135,6 +136,18 @@ fwrite(Format, Args) -> format(Format, Args). +-type chars_limit() :: integer(). + +-spec fwrite(Format, Data, Options) -> chars() when + Format :: io:format(), + Data :: [term()], + Options :: [Option], + Option :: {'chars_limit', CharsLimit}, + CharsLimit :: chars_limit(). + +fwrite(Format, Args, Options) -> + format(Format, Args, Options). + -spec fread(Format, String) -> Result when Format :: string(), String :: string(), @@ -165,11 +178,26 @@ fread(Cont, Chars, Format) -> Data :: [term()]. format(Format, Args) -> - case catch io_lib_format:fwrite(Format, Args) of - {'EXIT',_} -> - erlang:error(badarg, [Format, Args]); - Other -> - Other + try io_lib_format:fwrite(Format, Args) + catch + C:R:S -> + test_modules_loaded(C, R, S), + erlang:error(badarg, [Format, Args]) + end. + +-spec format(Format, Data, Options) -> chars() when + Format :: io:format(), + Data :: [term()], + Options :: [Option], + Option :: {'chars_limit', CharsLimit}, + CharsLimit :: chars_limit(). + +format(Format, Args, Options) -> + try io_lib_format:fwrite(Format, Args, Options) + catch + C:R:S -> + test_modules_loaded(C, R, S), + erlang:error(badarg, [Format, Args]) end. -spec scan_format(Format, Data) -> FormatList when @@ -180,7 +208,9 @@ format(Format, Args) -> scan_format(Format, Args) -> try io_lib_format:scan(Format, Args) catch - _:_ -> erlang:error(badarg, [Format, Args]) + C:R:S -> + test_modules_loaded(C, R, S), + erlang:error(badarg, [Format, Args]) end. -spec unscan_format(FormatList) -> {Format, Data} when @@ -195,7 +225,37 @@ unscan_format(FormatList) -> FormatList :: [char() | format_spec()]. build_text(FormatList) -> - io_lib_format:build(FormatList). + try io_lib_format:build(FormatList) + catch + C:R:S -> + test_modules_loaded(C, R, S), + erlang:error(badarg, [FormatList]) + end. + +-spec build_text(FormatList, Options) -> chars() when + FormatList :: [char() | format_spec()], + Options :: [Option], + Option :: {'chars_limit', CharsLimit}, + CharsLimit :: chars_limit(). + +build_text(FormatList, Options) -> + try io_lib_format:build(FormatList, Options) + catch + C:R:S -> + test_modules_loaded(C, R, S), + erlang:error(badarg, [FormatList, Options]) + end. + +%% Failure to load a module must not be labeled as badarg. +%% C, R, and S are included so that the original error, which could be +%% a bug in io_lib_format, can be found by tracing on +%% test_modules_loaded/3. +test_modules_loaded(_C, _R, _S) -> + Modules = [io_lib_format, io_lib_pretty, string, unicode], + case code:ensure_modules_loaded(Modules) of + ok -> ok; + Error -> erlang:error(Error) + end. -spec print(Term) -> chars() when Term :: term(). @@ -240,7 +300,7 @@ format_prompt(Prompt, Encoding) -> do_format_prompt(add_modifier(Encoding, "p"), [Prompt]). do_format_prompt(Format, Args) -> - case catch io_lib:format(Format, Args) of + case catch format(Format, Args) of {'EXIT',_} -> "???"; List -> List end. @@ -259,7 +319,8 @@ add_modifier(_, C) -> -spec write(Term) -> chars() when Term :: term(). -write(Term) -> write(Term, -1). +write(Term) -> + write1(Term, -1, latin1). -spec write(term(), depth(), boolean()) -> chars(). @@ -274,16 +335,29 @@ write(Term, D, false) -> (Term, Options) -> chars() when Term :: term(), Options :: [Option], - Option :: {'depth', Depth} + Option :: {'chars_limit', CharsLimit} + | {'depth', Depth} | {'encoding', 'latin1' | 'utf8' | 'unicode'}, + CharsLimit :: chars_limit(), Depth :: depth(). write(Term, Options) when is_list(Options) -> Depth = get_option(depth, Options, -1), Encoding = get_option(encoding, Options, epp:default_encoding()), - write1(Term, Depth, Encoding); + CharsLimit = get_option(chars_limit, Options, -1), + if + Depth =:= 0; CharsLimit =:= 0 -> + "..."; + CharsLimit < 0 -> + write1(Term, Depth, Encoding); + CharsLimit > 0 -> + RecDefFun = fun(_, _) -> no end, + If = io_lib_pretty:intermediate + (Term, Depth, CharsLimit, RecDefFun, Encoding, _Str=false), + io_lib_pretty:write(If) + end; write(Term, Depth) -> - write1(Term, Depth, latin1). + write(Term, [{depth, Depth}, {encoding, latin1}]). write1(_Term, 0, _E) -> "..."; write1(Term, _D, _E) when is_integer(Term) -> integer_to_list(Term); @@ -300,7 +374,7 @@ write1([H|T], D, E) -> if D =:= 1 -> "[...]"; true -> - [$[,[write1(H, D-1, E)|write_tail(T, D-1, E, $|)],$]] + [$[,[write1(H, D-1, E)|write_tail(T, D-1, E)],$]] end; write1(F, _D, _E) when is_function(F) -> erlang:fun_to_list(F); @@ -311,20 +385,24 @@ write1(T, D, E) when is_tuple(T) -> D =:= 1 -> "{...}"; true -> [${, - [write1(element(1, T), D-1, E)| - write_tail(tl(tuple_to_list(T)), D-1, E, $,)], + [write1(element(1, T), D-1, E)|write_tuple(T, 2, D-1, E)], $}] end. -%% write_tail(List, Depth, CharacterBeforeDots) +%% write_tail(List, Depth, Encoding) %% Test the terminating case first as this looks better with depth. -write_tail([], _D, _E, _S) -> ""; -write_tail(_, 1, _E, S) -> [S | "..."]; -write_tail([H|T], D, E, S) -> - [$,,write1(H, D-1, E)|write_tail(T, D-1, E, S)]; -write_tail(Other, D, E, S) -> - [S,write1(Other, D-1, E)]. +write_tail([], _D, _E) -> ""; +write_tail(_, 1, _E) -> [$| | "..."]; +write_tail([H|T], D, E) -> + [$,,write1(H, D-1, E)|write_tail(T, D-1, E)]; +write_tail(Other, D, E) -> + [$|,write1(Other, D-1, E)]. + +write_tuple(T, I, _D, _E) when I > tuple_size(T) -> ""; +write_tuple(_, _I, 1, _E) -> [$, | "..."]; +write_tuple(T, I, D, E) -> + [$,,write1(element(I, T), D-1, E)|write_tuple(T, I+1, D-1, E)]. write_port(Port) -> erlang:port_to_list(Port). @@ -333,32 +411,43 @@ write_ref(Ref) -> erlang:ref_to_list(Ref). write_map(Map, D, E) when is_integer(D) -> - [$#,${,write_map_body(maps:to_list(Map), D, E),$}]. + [$#,${,write_map_body(maps:to_list(Map), D, D - 1, E),$}]. -write_map_body(_, 0, _E) -> "..."; -write_map_body([], _, _E) -> []; -write_map_body([{K,V}], D, E) -> write_map_assoc(K, V, D, E); -write_map_body([{K,V}|KVs], D, E) -> - [write_map_assoc(K, V, D, E),$, | write_map_body(KVs, D-1, E)]. +write_map_body(_, 1, _D0, _E) -> "..."; +write_map_body([], _, _D0, _E) -> []; +write_map_body([{K,V}], _D, D0, E) -> write_map_assoc(K, V, D0, E); +write_map_body([{K,V}|KVs], D, D0, E) -> + [write_map_assoc(K, V, D0, E),$, | write_map_body(KVs, D - 1, D0, E)]. write_map_assoc(K, V, D, E) -> - [write1(K, D - 1, E),"=>",write1(V, D-1, E)]. + [write1(K, D, E)," => ",write1(V, D, E)]. write_binary(B, D) when is_integer(D) -> - [$<,$<,write_binary_body(B, D),$>,$>]. - -write_binary_body(<<>>, _D) -> - ""; -write_binary_body(_B, 1) -> - "..."; -write_binary_body(<<X:8>>, _D) -> - [integer_to_list(X)]; -write_binary_body(<<X:8,Rest/bitstring>>, D) -> - [integer_to_list(X),$,|write_binary_body(Rest, D-1)]; -write_binary_body(B, _D) -> + {S, _} = write_binary(B, D, -1), + S. + +write_binary(B, D, T) -> + {S, Rest} = write_binary_body(B, D, tsub(T, 4), []), + {[$<,$<,lists:reverse(S),$>,$>], Rest}. + +write_binary_body(<<>> = B, _D, _T, Acc) -> + {Acc, B}; +write_binary_body(B, D, T, Acc) when D =:= 1; T =:= 0-> + {["..."|Acc], B}; +write_binary_body(<<X:8>>, _D, _T, Acc) -> + {[integer_to_list(X)|Acc], <<>>}; +write_binary_body(<<X:8,Rest/bitstring>>, D, T, Acc) -> + S = integer_to_list(X), + write_binary_body(Rest, D-1, tsub(T, length(S) + 1), [$,,S|Acc]); +write_binary_body(B, _D, _T, Acc) -> L = bit_size(B), <<X:L>> = B, - [integer_to_list(X),$:,integer_to_list(L)]. + {[integer_to_list(L),$:,integer_to_list(X)|Acc], <<>>}. + +%% Make sure T does not change sign. +tsub(T, _) when T < 0 -> T; +tsub(T, E) when T >= E -> T - E; +tsub(_, _) -> 0. get_option(Key, TupleList, Default) -> case lists:keyfind(Key, 1, TupleList) of @@ -931,7 +1020,7 @@ limit_term(Term, Depth) -> limit(_, 0) -> '...'; limit([H|T]=L, D) -> if - D =:= 1 -> '...'; + D =:= 1 -> ['...']; true -> case printable_list(L) of true -> L; @@ -944,10 +1033,10 @@ limit(Term, D) when is_map(Term) -> limit({}=T, _D) -> T; limit(T, D) when is_tuple(T) -> if - D =:= 1 -> '...'; + D =:= 1 -> {'...'}; true -> list_to_tuple([limit(element(1, T), D-1)| - limit_tail(tl(tuple_to_list(T)), D-1)]) + limit_tuple(T, 2, D-1)]) end; limit(<<_/bitstring>>=Term, D) -> limit_bitstring(Term, D); limit(Term, _D) -> Term. @@ -959,23 +1048,36 @@ limit_tail([H|T], D) -> limit_tail(Other, D) -> limit(Other, D-1). +limit_tuple(T, I, _D) when I > tuple_size(T) -> []; +limit_tuple(_, _I, 1) -> ['...']; +limit_tuple(T, I, D) -> + [limit(element(I, T), D-1)|limit_tuple(T, I+1, D-1)]. + %% Cannot limit maps properly since there is no guarantee that %% maps:from_list() creates a map with the same internal ordering of -%% the selected associations as in Map. +%% the selected associations as in Map. Instead of subtracting one +%% from the depth as the map associations are traversed (as is done +%% for tuples and lists), the same depth is applied to each and every +%% (returned) association. limit_map(Map, D) -> - maps:from_list(erts_internal:maps_to_list(Map, D)). -%% maps:from_list(limit_map_body(erts_internal:maps_to_list(Map, D), D)). - -%% limit_map_body(_, 0) -> [{'...', '...'}]; -%% limit_map_body([], _) -> []; -%% limit_map_body([{K,V}], D) -> [limit_map_assoc(K, V, D)]; -%% limit_map_body([{K,V}|KVs], D) -> -%% [limit_map_assoc(K, V, D) | limit_map_body(KVs, D-1)]. + %% Keep one extra association to make sure the final ',...' is included. + limit_map_body(maps:iterator(Map), D + 1, D, []). + +limit_map_body(_I, 0, _D0, Acc) -> + maps:from_list(Acc); +limit_map_body(I, D, D0, Acc) -> + case maps:next(I) of + {K, V, NextI} -> + limit_map_body(NextI, D-1, D0, [limit_map_assoc(K, V, D0) | Acc]); + none -> + maps:from_list(Acc) + end. -%% limit_map_assoc(K, V, D) -> -%% {limit(K, D-1), limit(V, D-1)}. +limit_map_assoc(K, V, D) -> + %% Keep keys as are to avoid creating duplicated keys. + {K, limit(V, D - 1)}. -limit_bitstring(B, _D) -> B. %% Keeps all printable binaries. +limit_bitstring(B, _D) -> B. % Keeps all printable binaries. test_limit(_, 0) -> throw(limit); test_limit([H|T]=L, D) when is_integer(D) -> @@ -1011,18 +1113,21 @@ test_limit_tuple(T, I, Sz, D) -> test_limit(element(I, T), D-1), test_limit_tuple(T, I+1, Sz, D-1). -test_limit_map(_Map, _D) -> ok. -%% test_limit_map_body(erts_internal:maps_to_list(Map, D), D). - -%% test_limit_map_body(_, 0) -> throw(limit); -%% test_limit_map_body([], _) -> ok; -%% test_limit_map_body([{K,V}], D) -> test_limit_map_assoc(K, V, D); -%% test_limit_map_body([{K,V}|KVs], D) -> -%% test_limit_map_assoc(K, V, D), -%% test_limit_map_body(KVs, D-1). +test_limit_map(Map, D) -> + test_limit_map_body(maps:iterator(Map), D). + +test_limit_map_body(_I, 0) -> throw(limit); % cannot happen +test_limit_map_body(I, D) -> + case maps:next(I) of + {K, V, NextI} -> + test_limit_map_assoc(K, V, D), + test_limit_map_body(NextI, D-1); + none -> + ok + end. -%% test_limit_map_assoc(K, V, D) -> -%% test_limit(K, D-1), -%% test_limit(V, D-1). +test_limit_map_assoc(K, V, D) -> + test_limit(K, D - 1), + test_limit(V, D - 1). test_limit_bitstring(_, _) -> ok. |