diff options
Diffstat (limited to 'lib/stdlib/src')
| -rw-r--r-- | lib/stdlib/src/io_lib.erl | 2 | ||||
| -rw-r--r-- | lib/stdlib/src/io_lib_pretty.erl | 653 | ||||
| -rw-r--r-- | lib/stdlib/src/shell.erl | 2 | 
3 files changed, 429 insertions, 228 deletions
| diff --git a/lib/stdlib/src/io_lib.erl b/lib/stdlib/src/io_lib.erl index e37c13093b..6be953f6ca 100644 --- a/lib/stdlib/src/io_lib.erl +++ b/lib/stdlib/src/io_lib.erl @@ -240,7 +240,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. diff --git a/lib/stdlib/src/io_lib_pretty.erl b/lib/stdlib/src/io_lib_pretty.erl index 89e1931d2d..656d2ddd41 100644 --- a/lib/stdlib/src/io_lib_pretty.erl +++ b/lib/stdlib/src/io_lib_pretty.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %%  -%% Copyright Ericsson AB 1996-2017. All Rights Reserved. +%% Copyright Ericsson AB 1996-2018. All Rights Reserved.  %%   %% Licensed under the Apache License, Version 2.0 (the "License");  %% you may not use this file except in compliance with the License. @@ -45,20 +45,23 @@ print(Term) ->  %% Used by the shell for printing records and for Unicode.  -type rec_print_fun() :: fun((Tag :: atom(), NFields :: non_neg_integer()) -> -                                  no | [FieldName :: atom()]). +                                  'no' | [FieldName :: atom()]).  -type column() :: integer(). +-type encoding() :: epp:source_encoding() | 'unicode'.  -type line_length() :: pos_integer().  -type depth() :: integer(). --type max_chars() :: integer(). +-type line_max_chars() :: integer(). +-type chars_limit() :: integer().  -type chars() :: io_lib:chars(). --type option() :: {column, column()} -                | {line_length, line_length()} -                | {depth, depth()} -                | {max_chars, max_chars()} -                | {record_print_fun, rec_print_fun()} -                | {strings, boolean()} -                | {encoding, latin1 | utf8 | unicode}. +-type option() :: {'chars_limit', chars_limit()} +                | {'column', column()} +                | {'depth', depth()} +                | {'encoding', encoding()} +                | {'line_length', line_length()} +                | {'line_max_chars', line_max_chars()} +                | {'record_print_fun', rec_print_fun()} +                | {'strings', boolean()}.  -type options() :: [option()].  -spec print(term(), rec_print_fun()) -> chars(); @@ -68,11 +71,12 @@ print(Term, Options) when is_list(Options) ->      Col = get_option(column, Options, 1),      Ll = get_option(line_length, Options, 80),      D = get_option(depth, Options, -1), -    M = get_option(max_chars, Options, -1), +    M = get_option(line_max_chars, Options, -1), +    T = get_option(chars_limit, Options, -1),      RecDefFun = get_option(record_print_fun, Options, no_fun),      Encoding = get_option(encoding, Options, epp:default_encoding()),      Strings = get_option(strings, Options, true), -    print(Term, Col, Ll, D, M, RecDefFun, Encoding, Strings); +    print(Term, Col, Ll, D, M, T, RecDefFun, Encoding, Strings);  print(Term, RecDefFun) ->      print(Term, -1, RecDefFun). @@ -84,35 +88,43 @@ print(Term, Depth, RecDefFun) ->  -spec print(term(), column(), line_length(), depth()) -> chars().  print(Term, Col, Ll, D) -> -    print(Term, Col, Ll, D, _M=-1, no_fun, latin1, true). +    print(Term, Col, Ll, D, _M=-1, _T=-1, no_fun, latin1, true).  -spec print(term(), column(), line_length(), depth(), rec_print_fun()) ->                     chars().  print(Term, Col, Ll, D, RecDefFun) ->      print(Term, Col, Ll, D, _M=-1, RecDefFun). --spec print(term(), column(), line_length(), depth(), max_chars(), +-spec print(term(), column(), line_length(), depth(), line_max_chars(),              rec_print_fun()) -> chars().  print(Term, Col, Ll, D, M, RecDefFun) -> -    print(Term, Col, Ll, D, M, RecDefFun, latin1, true). +    print(Term, Col, Ll, D, M, _T=-1, RecDefFun, latin1, true).  %% D = Depth, default -1 (infinite), or LINEMAX=30 when printing from shell +%% T = chars_limit, that is, maximal number of characters, default -1 +%%   Used together with D to limit the output. It is possible that +%%   more than T characters are returned.  %% Col = current column, default 1  %% Ll = line length/~p field width, default 80  %% M = CHAR_MAX (-1 if no max, 60 when printing from shell) -print(_, _, _, 0, _M, _RF, _Enc, _Str) -> "..."; -print(Term, Col, Ll, D, M, RecDefFun, Enc, Str) when Col =< 0 -> +print(_, _, _, 0, _M, _T, _RF, _Enc, _Str) -> "..."; +print(_, _, _, _D, _M, 0, _RF, _Enc, _Str) -> "..."; +print(Term, Col, Ll, D, M, T, RecDefFun, Enc, Str) when Col =< 0 ->      %% ensure Col is at least 1 -    print(Term, 1, Ll, D, M, RecDefFun, Enc, Str); -print(Atom, _Col, _Ll, _D, _M, _RF, Enc, _Str) when is_atom(Atom) -> +    print(Term, 1, Ll, D, M, T, RecDefFun, Enc, Str); +print(Atom, _Col, _Ll, _D, _M, _T, _RF, Enc, _Str) when is_atom(Atom) ->      write_atom(Atom, Enc); -print(Term, Col, Ll, D, M0, RecDefFun, Enc, Str) when is_tuple(Term); -                                                      is_list(Term); -                                                      is_map(Term); -                                                      is_bitstring(Term) -> +print(Term, Col, Ll, D, M0, T, RecDefFun, Enc, Str) when is_tuple(Term); +                                                         is_list(Term); +                                                         is_map(Term); +                                                         is_bitstring(Term) ->      %% preprocess and compute total number of chars -    If = {_S, Len} = print_length(Term, D, RecDefFun, Enc, Str), +    {_, Len, _Dots, _} = If = +        case T < 0 of +            true -> print_length(Term, D, T, RecDefFun, Enc, Str); +            false -> intermediate(Term, D, T, RecDefFun, Enc, Str) +        end,      %% use Len as CHAR_MAX if M0 = -1      M = max_cs(M0, Len),      if @@ -126,7 +138,7 @@ print(Term, Col, Ll, D, M0, RecDefFun, Enc, Str) when is_tuple(Term);                                1),              pp(If, Col, Ll, M, TInd, indent(Col), 0, 0)      end; -print(Term, _Col, _Ll, _D, _M, _RF, _Enc, _Str) -> +print(Term, _Col, _Ll, _D, _M, _T, _RF, _Enc, _Str) ->      %% atomic data types (bignums, atoms, ...) are never truncated      io_lib:write(Term). @@ -147,28 +159,28 @@ max_cs(M, _Len) ->          ?ATM(element(3, element(1, Pair)))). % Value  -define(ATM_FLD(Field), ?ATM(element(4, element(1, Field)))). -pp({_S, Len} = If, Col, Ll, M, _TInd, _Ind, LD, W)  +pp({_S,Len,_,_} = If, Col, Ll, M, _TInd, _Ind, LD, W)                        when Len < Ll - Col - LD, Len + W + LD =< M ->      write(If); -pp({{list,L}, _Len}, Col, Ll, M, TInd, Ind, LD, W) -> +pp({{list,L}, _Len, _, _}, Col, Ll, M, TInd, Ind, LD, W) ->      [$[, pp_list(L, Col + 1, Ll, M, TInd, indent(1, Ind), LD, $|, W + 1), $]]; -pp({{tuple,true,L}, _Len}, Col, Ll, M, TInd, Ind, LD, W) -> +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({{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({{map,Pairs}, _Len, _, _}, Col, Ll, M, TInd, Ind, LD, W) ->      [$#, ${, pp_map(Pairs, Col + 2, Ll, M, TInd, indent(2, Ind), LD, W + 1),       $}]; -pp({{record,[{Name,NLen} | L]}, _Len}, 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) -> +pp({{bin,S}, _Len, _, _}, Col, Ll, M, _TInd, Ind, LD, W) ->      pp_binary(S, Col + 2, Ll, M, indent(2, Ind), LD, W); -pp({S, _Len}, _Col, _Ll, _M, _TInd, _Ind, _LD, _W) -> +pp({S,_Len,_,_}, _Col, _Ll, _M, _TInd, _Ind, _LD, _W) ->      S.  %%  Print a tagged tuple by indenting the rest of the elements  %%  differently to the tag. Tuple has size >= 2. -pp_tag_tuple([{Tag,Tlen} | L], Col, Ll, M, TInd, Ind, LD, W) -> +pp_tag_tuple([{Tag,Tlen,_,_} | L], Col, Ll, M, TInd, Ind, LD, W) ->      %% this uses TInd      TagInd = Tlen + 2,      Tcol = Col + TagInd, @@ -184,18 +196,18 @@ pp_tag_tuple([{Tag,Tlen} | L], Col, Ll, M, TInd, Ind, LD, W) ->      end.  pp_map([], _Col, _Ll, _M, _TInd, _Ind, _LD, _W) -> -    ""; -pp_map({dots, _}, _Col, _Ll, _M, _TInd, _Ind, _LD, _W) -> -    "..."; +    "";                                         % cannot happen +pp_map({dots, _, _, _}, _Col, _Ll, _M, _TInd, _Ind, _LD, _W) -> +    "...";                                      % cannot happen  pp_map([P | Ps], Col, Ll, M, TInd, Ind, LD, W) ->      {PS, PW} = pp_pair(P, Col, Ll, M, TInd, Ind, last_depth(Ps, LD), W),      [PS | pp_pairs_tail(Ps, Col, Col + PW, Ll, M, TInd, Ind, LD, PW)].  pp_pairs_tail([], _Col0, _Col, _Ll, _M, _TInd, _Ind, _LD, _W) ->      ""; -pp_pairs_tail({dots, _}, _Col0, _Col, _M, _Ll, _TInd, _Ind, _LD, _W) -> +pp_pairs_tail({dots, _, _, _}, _Col0, _Col, _M, _Ll, _TInd, _Ind, _LD, _W) ->      ",..."; -pp_pairs_tail([{_, Len}=P | Ps], Col0, Col, Ll, M, TInd, Ind, LD, W) -> +pp_pairs_tail([{_, Len, _, _}=P | Ps], Col0, Col, Ll, M, TInd, Ind, LD, W) ->      LD1 = last_depth(Ps, LD),      ELen = 1 + Len,      if @@ -209,7 +221,7 @@ pp_pairs_tail([{_, Len}=P | Ps], Col0, Col, Ll, M, TInd, Ind, LD, W) ->               pp_pairs_tail(Ps, Col0, Col0 + PW, Ll, M, TInd, Ind, LD, PW)]      end. -pp_pair({_, Len}=Pair, Col, Ll, M, _TInd, _Ind, LD, W) +pp_pair({_, Len, _, _}=Pair, Col, Ll, M, _TInd, _Ind, LD, W)           when Len < Ll - Col - LD, Len + W + LD =< M ->      {write_pair(Pair), if                            ?ATM_PAIR(Pair) -> @@ -217,7 +229,7 @@ pp_pair({_, Len}=Pair, Col, Ll, M, _TInd, _Ind, LD, W)                            true ->                                Ll % force nl                        end}; -pp_pair({{map_pair, K, V}, _Len}, Col0, Ll, M, TInd, Ind0, LD, W) -> +pp_pair({{map_pair, K, V}, _Len, _, _}, Col0, Ll, M, TInd, Ind0, LD, W) ->      I = map_value_indent(TInd),      Ind = indent(I, Ind0),      {[pp(K, Col0, Ll, M, TInd, Ind0, LD, W), " =>\n", @@ -225,7 +237,7 @@ pp_pair({{map_pair, K, V}, _Len}, Col0, Ll, M, TInd, Ind0, LD, W) ->  pp_record([], _Nlen, _Col, _Ll, _M, _TInd, _Ind, _LD, _W) ->      ""; -pp_record({dots, _}, _Nlen, _Col, _Ll, _M, _TInd, _Ind, _LD, _W) -> +pp_record({dots, _, _, _}, _Nlen, _Col, _Ll, _M, _TInd, _Ind, _LD, _W) ->      "...";  pp_record([F | Fs], Nlen, Col0, Ll, M, TInd, Ind0, LD, W0) ->      Nind = Nlen + 1, @@ -235,9 +247,9 @@ pp_record([F | Fs], Nlen, Col0, Ll, M, TInd, Ind0, LD, W0) ->  pp_fields_tail([], _Col0, _Col, _Ll, _M, _TInd, _Ind, _LD, _W) ->      ""; -pp_fields_tail({dots, _}, _Col0, _Col, _M, _Ll, _TInd, _Ind, _LD, _W) -> +pp_fields_tail({dots, _, _ ,_}, _Col0, _Col, _M, _Ll, _TInd, _Ind, _LD, _W) ->      ",..."; -pp_fields_tail([{_, Len}=F | Fs], Col0, Col, Ll, M, TInd, Ind, LD, W) -> +pp_fields_tail([{_, Len, _, _}=F | Fs], Col0, Col, Ll, M, TInd, Ind, LD, W) ->      LD1 = last_depth(Fs, LD),      ELen = 1 + Len,      if @@ -251,7 +263,7 @@ pp_fields_tail([{_, Len}=F | Fs], Col0, Col, Ll, M, TInd, Ind, LD, W) ->               pp_fields_tail(Fs, Col0, Col0 + FW, Ll, M, TInd, Ind, LD, FW)]      end. -pp_field({_, Len}=Fl, Col, Ll, M, _TInd, _Ind, LD, W)  +pp_field({_, Len, _, _}=Fl, Col, Ll, M, _TInd, _Ind, LD, W)           when Len < Ll - Col - LD, Len + W + LD =< M ->      {write_field(Fl), if                            ?ATM_FLD(Fl) ->  @@ -259,7 +271,7 @@ pp_field({_, Len}=Fl, Col, Ll, M, _TInd, _Ind, LD, W)                            true ->                                 Ll % force nl                        end}; -pp_field({{field, Name, NameL, F}, _Len}, Col0, Ll, M, TInd, Ind0, LD, W0) -> +pp_field({{field, Name, NameL, F},_,_, _}, Col0, Ll, M, TInd, Ind0, LD, W0) ->      {Col, Ind, S, W} = rec_indent(NameL, TInd, Col0, Ind0, W0 + NameL),      Sep = case S of                [$\n | _] -> " ="; @@ -286,15 +298,15 @@ rec_indent(RInd, TInd, Col0, Ind0, W0) ->          end,      {Col, Ind, S, W}. -pp_list({dots, _}, _Col0, _Ll, _M, _TInd, _Ind, _LD, _S, _W) -> +pp_list({dots, _, _, _}, _Col0, _Ll, _M, _TInd, _Ind, _LD, _S, _W) ->      "...";  pp_list([E | Es], Col0, Ll, M, TInd, Ind, LD, S, W) ->      {ES, WE} = pp_element(E, Col0, Ll, M, TInd, Ind, last_depth(Es, LD), W),      [ES | pp_tail(Es, Col0, Col0 + WE, Ll, M, TInd, Ind, LD, S, W + WE)].  pp_tail([], _Col0, _Col, _Ll, _M, _TInd, _Ind, _LD, _S, _W) -> -    ""; -pp_tail([{_, Len}=E | Es], Col0, Col, Ll, M, TInd, Ind, LD, S, W) -> +    []; +pp_tail([{_, Len, _, _}=E | Es], Col0, Col, Ll, M, TInd, Ind, LD, S, W) ->      LD1 = last_depth(Es, LD),      ELen = 1 + Len,      if  @@ -307,9 +319,9 @@ pp_tail([{_, Len}=E | Es], Col0, Col, Ll, M, TInd, Ind, LD, S, W) ->              [$,, $\n, Ind, ES |                pp_tail(Es, Col0, Col0 + WE, Ll, M, TInd, Ind, LD, S, WE)]      end; -pp_tail({dots, _}, _Col0, _Col, _Ll, _M, _TInd, _Ind, _LD, S, _W) -> +pp_tail({dots, _, _, _}, _Col0, _Col, _Ll, _M, _TInd, _Ind, _LD, S, _W) ->      [S | "..."]; -pp_tail({_, Len}=E, _Col0, Col, Ll, M, _TInd, _Ind, LD, S, W)  +pp_tail({_, Len, _, _}=E, _Col0, Col, Ll, M, _TInd, _Ind, LD, S, W)                    when Len + 1 < Ll - Col - (LD + 1),                          Len + 1 + W + (LD + 1) =< M,                          ?ATM(E) -> @@ -317,7 +329,7 @@ pp_tail({_, Len}=E, _Col0, Col, Ll, M, _TInd, _Ind, LD, S, W)  pp_tail(E, Col0, _Col, Ll, M, TInd, Ind, LD, S, _W) ->      [S, $\n, Ind | pp(E, Col0, Ll, M, TInd, Ind, LD + 1, 0)]. -pp_element({_, Len}=E, Col, Ll, M, _TInd, _Ind, LD, W)  +pp_element({_, Len, _, _}=E, Col, Ll, M, _TInd, _Ind, LD, W)             when Len < Ll - Col - LD, Len + W + LD =< M, ?ATM(E) ->      {write(E), Len};  pp_element(E, Col, Ll, M, TInd, Ind, LD, W) -> @@ -348,42 +360,42 @@ pp_binary(S, N, _N0, Ind) ->      end.  %% write the whole thing on a single line -write({{tuple, _IsTagged, L}, _}) -> +write({{tuple, _IsTagged, L}, _, _, _}) ->      [${, write_list(L, $,), $}]; -write({{list, L}, _}) -> +write({{list, L}, _, _, _}) ->      [$[, write_list(L, $|), $]]; -write({{map, Pairs}, _}) -> +write({{map, Pairs}, _, _, _}) ->      [$#,${, write_list(Pairs, $,), $}]; -write({{map_pair, _K, _V}, _}=Pair) -> +write({{map_pair, _K, _V}, _, _, _}=Pair) ->      write_pair(Pair); -write({{record, [{Name,_} | L]}, _}) -> +write({{record, [{Name,_} | L]}, _, _, _}) ->      [Name, ${, write_fields(L), $}]; -write({{bin, S}, _}) -> +write({{bin, S}, _, _, _}) ->      S; -write({S, _}) -> +write({S, _, _, _}) ->      S. -write_pair({{map_pair, K, V}, _}) -> +write_pair({{map_pair, K, V}, _, _, _}) ->      [write(K), " => ", write(V)].  write_fields([]) ->      ""; -write_fields({dots, _}) -> +write_fields({dots, _, _, _}) ->      "...";  write_fields([F | Fs]) ->      [write_field(F) | write_fields_tail(Fs)].  write_fields_tail([]) ->      ""; -write_fields_tail({dots, _}) -> +write_fields_tail({dots, _, _, _}) ->      ",...";  write_fields_tail([F | Fs]) ->      [$,, write_field(F) | write_fields_tail(Fs)]. -write_field({{field, Name, _NameL, F}, _}) -> +write_field({{field, Name, _NameL, F}, _, _, _}) ->      [Name, " = " | write(F)]. -write_list({dots, _}, _S) -> +write_list({dots, _, _, _}, _S) ->      "...";  write_list([E | Es], S) ->      [write(E) | write_tail(Es, S)]. @@ -392,192 +404,339 @@ write_tail([], _S) ->      [];  write_tail([E | Es], S) ->      [$,, write(E) | write_tail(Es, S)]; -write_tail({dots, _}, S) -> +write_tail({dots, _, _, _}, S) ->      [S | "..."];  write_tail(E, S) ->      [S | write(E)]. +-type more() :: fun((chars_limit(), DeltaDepth :: non_neg_integer()) -> +                            intermediate_format()). + +-type if_list() :: maybe_improper_list(intermediate_format(), +                                       {'dots', non_neg_integer(), +                                        non_neg_integer(), more()}). + +-type intermediate_format() :: +        {chars() +         | {'bin', chars()} +         | 'dots' +         | {'field', Name :: chars(), NameLen :: non_neg_integer(), +                     intermediate_format()} +         | {'list', if_list()} +         | {'map', if_list()} +         | {'map_pair', K :: intermediate_format(), +                        V :: intermediate_format()} +         | {'record', [{Name :: chars(), NameLen :: non_neg_integer()} +                       | if_list()]} +         | {'tuple', IsTagged :: boolean(), if_list()}, +         Len :: non_neg_integer(), +         NumOfDots :: non_neg_integer(), +         More :: more() | 'no_more' +        }. + +-spec intermediate(term(), depth(), chars_limit(), rec_print_fun(), +                   encoding(), boolean()) -> intermediate_format(). + +intermediate(Term, D, T, RF, Enc, Str) when T >= 0 -> +    D0 = 1, +    If = print_length(Term, D0, T, RF, Enc, Str), +    case If of +        {_, Len, Dots, _} when Dots =:= 0; Len > T; D =:= 1 -> +            If; +        _ -> +            find_upper(If, Term, T, D0, 2, D, RF, Enc, Str) +    end. + +find_upper(Lower, Term, T, Dl, Dd, D, RF, Enc, Str) -> +    Dd2 = Dd * 2, +    D1 = case D < 0 of +             true -> Dl + Dd2; +             false -> min(Dl + Dd2, D) +         end, +    If = expand(Lower, T, D1 - Dl), +    case If of +        {_, _, _Dots=0, _} -> % even if Len > T +            If; +        {_, Len, _, _} when Len =< T, D1 < D orelse D < 0 -> +	    find_upper(If, Term, T, D1, Dd2, D, RF, Enc, Str); +        _ -> +	    search_depth(Lower, If, Term, T, Dl, D1, RF, Enc, Str) +    end. + +%% Lower has NumOfDots > 0 and Len =< T. +%% Upper has NumOfDots > 0 and Len > T. +search_depth(Lower, Upper, _Term, T, Dl, Du, _RF, _Enc, _Str) +        when Du - Dl =:= 1 -> +    %% The returned intermediate format has Len >= T. +    case Lower of +        {_, T, _, _} -> +            Lower; +        _ -> +            Upper +    end; +search_depth(Lower, Upper, Term, T, Dl, Du, RF, Enc, Str) -> +    D1 = (Dl  + Du) div 2, +    If = expand(Lower, T, D1 - Dl), +    case If of +	{_, Len, _, _} when Len > T -> +            %% Len can be greater than Upper's length. +            %% This is a bit expensive since the work to +            %% crate Upper is wasted. It is the price +            %% to pay to get a more balanced output. +            search_depth(Lower, If, Term, T, Dl, D1, RF, Enc, Str); +        _ -> +            search_depth(If, Upper, Term, T, D1, Du, RF, Enc, Str) +    end. +  %% The depth (D) is used for extracting and counting the characters to  %% print. The structure is kept so that the returned intermediate  %% format can be formatted. The separators (list, tuple, record, map) are  %% counted but need to be added later.  %% D =/= 0 -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(Atom, _D, _RF, Enc, _Str) when is_atom(Atom) -> +print_length([], _D, _T, _RF, _Enc, _Str) -> +    {"[]", 2, 0, no_more}; +print_length({}, _D, _T, _RF, _Enc, _Str) -> +    {"{}", 2, 0, no_more}; +print_length(#{}=M, _D, _T, _RF, _Enc, _Str) when map_size(M) =:= 0 -> +    {"#{}", 3, 0, no_more}; +print_length(Atom, _D, _T, _RF, Enc, _Str) when is_atom(Atom) ->      S = write_atom(Atom, Enc), -    {S, lists:flatlength(S)}; -print_length(List, D, RF, Enc, Str) when is_list(List) -> +    {S, string:length(S), 0, no_more}; +print_length(List, D, T, RF, Enc, Str) when is_list(List) ->      %% only flat lists are "printable" -    case Str andalso printable_list(List, D, Enc) of +    case Str andalso printable_list(List, D, T, Enc) of          true ->              %% print as string, escaping double-quotes in the list              S = write_string(List, Enc), -            {S, length(S)}; -        %% Truncated lists could break some existing code. -        % {true, Prefix} -> -        %    S = write_string(Prefix, Enc), -        %    {[S | "..."], 3 + length(S)}; +            {S, length(S), 0, no_more}; +        {true, Prefix} -> +            %% Truncated lists when T < 0 could break some existing code. +            S = write_string(Prefix, Enc), +            %% NumOfDots = 0 to avoid looping--increasing the depth +            %% does not make Prefix longer. +            {[S | "..."], 3 + length(S), 0, no_more};          false -> -            print_length_list(List, D, RF, Enc, Str) +            case print_length_list(List, D, T, RF, Enc, Str) of +                {What, Len, Dots, _More} when Dots > 0 -> +                    More = fun(T1, Dd) -> +                                   ?FUNCTION_NAME(List, D+Dd, T1, RF, Enc, Str) +                           end, +                    {What, Len, Dots, More}; +                If -> +                    If +            end      end; -print_length(Fun, _D, _RF, _Enc, _Str) when is_function(Fun) -> +print_length(Fun, _D, _T, _RF, _Enc, _Str) when is_function(Fun) ->      S = io_lib:write(Fun), -    {S, iolist_size(S)}; -print_length(R, D, RF, Enc, Str) when is_atom(element(1, R)), -                                      is_function(RF) -> +    {S, iolist_size(S), 0, no_more}; +print_length(R, D, T, RF, Enc, Str) when is_atom(element(1, R)), +                                         is_function(RF) ->      case RF(element(1, R), tuple_size(R) - 1) of          no ->  -            print_length_tuple(R, D, RF, Enc, Str); +            print_length_tuple(R, D, T, RF, Enc, Str);          RDefs -> -            print_length_record(R, D, RF, RDefs, Enc, Str) +            print_length_record(R, D, T, RF, RDefs, Enc, Str)      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) -> -    {"<<...>>", 7}; -print_length(<<_/bitstring>>=Bin, D, _RF, Enc, Str) -> -    case bit_size(Bin) rem 8 of -        0 -> -	    D1 = D - 1,  -	    case Str andalso printable_bin(Bin, D1, Enc) of -                {true, List} when is_list(List) -> -                    S = io_lib:write_string(List, $"), %" -	            {[$<,$<,S,$>,$>], 4 + length(S)}; -                {false, List} when is_list(List) -> -                    S = io_lib:write_string(List, $"), %" -	            {[$<,$<,S,"/utf8>>"], 9 + length(S)}; -	        {true, true, Prefix} -> -	            S = io_lib:write_string(Prefix, $"), %" -	            {[$<,$<, S | "...>>"], 7 + length(S)}; -	        {false, true, Prefix} -> -                    S = io_lib:write_string(Prefix, $"), %" -	            {[$<,$<, S | "/utf8...>>"], 12 + length(S)}; -	        false -> -	            S = io_lib:write(Bin, D), -	            {{bin,S}, iolist_size(S)} -	    end; -        _ -> -           S = io_lib:write(Bin, D), -	   {{bin,S}, iolist_size(S)} +print_length(Tuple, D, T, RF, Enc, Str) when is_tuple(Tuple) -> +    print_length_tuple(Tuple, D, T, RF, Enc, Str); +print_length(Map, D, T, RF, Enc, Str) when is_map(Map) -> +    print_length_map(Map, D, T, RF, Enc, Str); +print_length(<<>>, _D, _T, _RF, _Enc, _Str) -> +    {"<<>>", 4, 0, no_more}; +print_length(<<_/bitstring>> = Bin, 1, _T, RF, Enc, Str) -> +    More = fun(T1, Dd) -> ?FUNCTION_NAME(Bin, 1+Dd, T1, RF, Enc, Str) end, +    {"<<...>>", 7, 3, More}; +print_length(<<_/bitstring>> = Bin, D, T, RF, Enc, Str) -> +    D1 = D - 1, +    case +        Str andalso +        (bit_size(Bin) rem 8) =:= 0 andalso +        printable_bin0(Bin, D1, tsub(T, 6), Enc) +    of +        {true, List} when is_list(List) -> +            S = io_lib:write_string(List, $"), %" +            {[$<,$<,S,$>,$>], 4 + length(S), 0, no_more}; +        {false, List} when is_list(List) -> +            S = io_lib:write_string(List, $"), %" +            {[$<,$<,S,"/utf8>>"], 9 + length(S), 0, no_more}; +        {true, true, Prefix} -> +            S = io_lib:write_string(Prefix, $"), %" +            More = fun(T1, Dd) -> +                           ?FUNCTION_NAME(Bin, D+Dd, T1, RF, Enc, Str) +                   end, +            {[$<,$<,S|"...>>"], 7 + length(S), 3, More}; +        {false, true, Prefix} -> +            S = io_lib:write_string(Prefix, $"), %" +            More = fun(T1, Dd) -> +                           ?FUNCTION_NAME(Bin, D+Dd, T1, RF, Enc, Str) +                   end, +            {[$<,$<,S|"/utf8...>>"], 12 + length(S), 3, More}; +        false when byte_size(Bin) < D -> +            S = io_lib:write(Bin, D), +            {{bin, S}, iolist_size(S), 0, no_more}; +        false -> +            S = io_lib:write(Bin, D), +            More = fun(T1, Dd) -> +                           ?FUNCTION_NAME(Bin, D+Dd, T1, RF, Enc, Str) +                   end, +            {{bin, S}, iolist_size(S), 3, More}      end;     -print_length(Term, _D, _RF, _Enc, _Str) -> +print_length(Term, _D, _T, _RF, _Enc, _Str) ->      S = io_lib:write(Term),      %% S can contain unicode, so iolist_size(S) cannot be used here -    {S, string:length(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(limit_map(maps:iterator(Map), D, []), D, RF, Enc, Str), -    {{map, Pairs}, list_length(Pairs, 3)}. - -limit_map(_I, 0, Acc) -> -    Acc; -limit_map(I, D, Acc) -> -    case maps:next(I) of -        {K, V, NextI} -> -            limit_map(NextI, D-1, [{K,V} | Acc]); -        none -> -            Acc -    end. - -print_length_map_pairs([], _D, _RF, _Enc, _Str) -> +    {S, string:length(S), 0, no_more}. + +print_length_map(Map, 1, _T, RF, Enc, Str) -> +    More = fun(T1, Dd) -> ?FUNCTION_NAME(Map, 1+Dd, T1, RF, Enc, Str) end, +    {"#{...}", 6, 3, More}; +print_length_map(Map, D, T, RF, Enc, Str) when is_map(Map) -> +    Next = maps:next(maps:iterator(Map)), +    PairsS = print_length_map_pairs(Next, D, tsub(T, 3), RF, Enc, Str), +    {Len, Dots} = list_length(PairsS, 3, 0), +    {{map, PairsS}, Len, Dots, no_more}. + +print_length_map_pairs(none, _D, _T, _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), +print_length_map_pairs(Term, D, T, RF, Enc, Str) when D =:= 1; T =:= 0-> +    More = fun(T1, Dd) -> ?FUNCTION_NAME(Term, D+Dd, T1, RF, Enc, Str) end, +    {dots, 3, 3, More}; +print_length_map_pairs({K, V, Iter}, D, T, RF, Enc, Str) -> +    Pair1 = print_length_map_pair(K, V, D - 1, tsub(T, 1), RF, Enc, Str), +    {_, Len1, _, _} = Pair1, +    Next = maps:next(Iter), +    [Pair1 | +     print_length_map_pairs(Next, D - 1, tsub(T, Len1+1), RF, Enc, Str)]. + +print_length_map_pair(K, V, D, T, RF, Enc, Str) -> +    {_, KL, KD, _} = P1 = print_length(K, D, T, RF, Enc, Str),      KL1 = KL + 4, -    {{map_pair, {KS, KL1}, {VS, VL}}, KL1 + VL}. - -print_length_tuple(_Tuple, 1, _RF, _Enc, _Str) -> -    {"{...}", 5}; -print_length_tuple(Tuple, D, RF, Enc, Str) -> -    L = print_length_list1(tuple_to_list(Tuple), D, RF, Enc, Str), +    {_, VL, VD, _} = P2 = print_length(V, D, tsub(T, KL1), RF, Enc, Str), +    {{map_pair, P1, P2}, KL1 + VL, KD + VD, no_more}. + +print_length_tuple(Tuple, 1, _T, RF, Enc, Str) -> +    More = fun(T1, Dd) -> ?FUNCTION_NAME(Tuple, 1+Dd, T1, RF, Enc, Str) end, +    {"{...}", 5, 3, More}; +print_length_tuple(Tuple, D, T, RF, Enc, Str) -> +    L = print_length_list1(tuple_to_list(Tuple), D, tsub(T, 2), RF, Enc, Str),      IsTagged = is_atom(element(1, Tuple)) and (tuple_size(Tuple) > 1), -    {{tuple,IsTagged,L}, list_length(L, 2)}. +    {Len, Dots} = list_length(L, 2, 0), +    {{tuple,IsTagged,L}, Len, Dots, no_more}. -print_length_record(_Tuple, 1, _RF, _RDefs, _Enc, _Str) -> -    {"{...}", 5}; -print_length_record(Tuple, D, RF, RDefs, Enc, Str) -> +print_length_record(Tuple, 1, _T, RF, RDefs, Enc, Str) -> +    More = fun(T1, Dd) -> +                   ?FUNCTION_NAME(Tuple, 1+Dd, T1, RF, RDefs, Enc, Str) +           end, +    {"{...}", 5, 3, More}; +print_length_record(Tuple, D, T, RF, RDefs, Enc, Str) ->      Name = [$# | write_atom(element(1, Tuple), Enc)], -    NameL = length(Name), +    NameL = string:length(Name),      Elements = tl(tuple_to_list(Tuple)), -    L = print_length_fields(RDefs, D - 1, Elements, RF, Enc, Str), -    {{record, [{Name,NameL} | L]}, list_length(L, NameL + 2)}. +    T1 = tsub(T, NameL+2), +    L = print_length_fields(RDefs, D - 1, T1, Elements, RF, Enc, Str), +    {Len, Dots} = list_length(L, NameL + 2, 0), +    {{record, [{Name,NameL} | L]}, Len, Dots, no_more}. -print_length_fields([], _D, [], _RF, _Enc, _Str) -> +print_length_fields([], _D, _T, [], _RF, _Enc, _Str) ->      []; -print_length_fields(_, 1, _, _RF, _Enc, _Str) -> -    {dots, 3}; -print_length_fields([Def | Defs], D, [E | Es], RF, Enc, Str) -> -    [print_length_field(Def, D - 1, E, RF, Enc, Str) | -     print_length_fields(Defs, D - 1, Es, RF, Enc, Str)]. - -print_length_field(Def, D, E, RF, Enc, Str) -> +print_length_fields(Term, D, T, Es, RF, Enc, Str) when D =:= 1; T =:= 0 -> +    More = fun(T1, Dd) -> +                   ?FUNCTION_NAME(Term, D+Dd, T1, Es, RF, Enc, Str) +           end, +    {dots, 3, 3, More}; +print_length_fields([Def | Defs], D, T, [E | Es], RF, Enc, Str) -> +    Field1 = print_length_field(Def, D - 1, tsub(T, 1), E, RF, Enc, Str), +    {_, Len1, _, _} = Field1, +    [Field1 | +     print_length_fields(Defs, D - 1, tsub(T, Len1 + 1), Es, RF, Enc, Str)]. + +print_length_field(Def, D, T, E, RF, Enc, Str) ->      Name = write_atom(Def, Enc), -    {S, L} = print_length(E, D, RF, Enc, Str), -    NameL = length(Name) + 3, -    {{field, Name, NameL, {S, L}}, NameL + L}. +    NameL = string:length(Name) + 3, +    {_, Len, Dots, _} = +        Field = print_length(E, D, tsub(T, NameL), RF, Enc, Str), +    {{field, Name, NameL, Field}, NameL + Len, Dots, no_more}. -print_length_list(List, D, RF, Enc, Str) -> -    L = print_length_list1(List, D, RF, Enc, Str), -    {{list, L}, list_length(L, 2)}. +print_length_list(List, D, T, RF, Enc, Str) -> +    L = print_length_list1(List, D, tsub(T, 2), RF, Enc, Str), +    {Len, Dots} = list_length(L, 2, 0), +    {{list, L}, Len, Dots, no_more}. -print_length_list1([], _D, _RF, _Enc, _Str) -> +print_length_list1([], _D, _T, _RF, _Enc, _Str) ->      []; -print_length_list1(_, 1, _RF, _Enc, _Str) -> -    {dots, 3}; -print_length_list1([E | Es], D, RF, Enc, Str) -> -    [print_length(E, D - 1, RF, Enc, Str) | -     print_length_list1(Es, D - 1, RF, Enc, Str)]; -print_length_list1(E, D, RF, Enc, Str) -> -    print_length(E, D - 1, RF, Enc, Str). - -list_length([], Acc) -> -    Acc; -list_length([{_, Len} | Es], Acc) -> -    list_length_tail(Es, Acc + Len); -list_length({_, Len}, Acc) -> -    Acc + Len. - -list_length_tail([], Acc) -> -    Acc; -list_length_tail([{_,Len} | Es], Acc) -> -    list_length_tail(Es, Acc + 1 + Len); -list_length_tail({_, Len}, Acc) -> -    Acc + 1 + Len. +print_length_list1(Term, D, T, RF, Enc, Str) when D =:= 1; T =:= 0-> +    More = fun(T1, Dd) -> ?FUNCTION_NAME(Term, D+Dd, T1, RF, Enc, Str) end, +    {dots, 3, 3, More}; +print_length_list1([E | Es], D, T, RF, Enc, Str) -> +    {_, Len1, _, _} = Elem1 = print_length(E, D - 1, tsub(T, 1), RF, Enc, Str), +    [Elem1 | print_length_list1(Es, D - 1, tsub(T, Len1 + 1), RF, Enc, Str)]; +print_length_list1(E, D, T, RF, Enc, Str) -> +    print_length(E, D - 1, T, RF, Enc, Str). + +list_length([], Acc, DotsAcc) -> +    {Acc, DotsAcc}; +list_length([{_, Len, Dots, _} | Es], Acc, DotsAcc) -> +    list_length_tail(Es, Acc + Len, DotsAcc + Dots); +list_length({_, Len, Dots, _}, Acc, DotsAcc) -> +    {Acc + Len, DotsAcc + Dots}. + +list_length_tail([], Acc, DotsAcc) -> +    {Acc, DotsAcc}; +list_length_tail([{_, Len, Dots, _} | Es], Acc, DotsAcc) -> +    list_length_tail(Es, Acc + 1 + Len, DotsAcc + Dots); +list_length_tail({_, Len, Dots, _}, Acc, DotsAcc) -> +    {Acc + 1 + Len, DotsAcc + Dots}.  %% ?CHARS printable characters has depth 1.  -define(CHARS, 4).  %% only flat lists are "printable" -printable_list(_L, 1, _Enc) -> +printable_list(_L, 1, _T, _Enc) ->      false; -printable_list(L, _D, latin1) -> +printable_list(L, _D, T, latin1) when T < 0 ->      io_lib:printable_latin1_list(L); -printable_list(L, _D, _Uni) -> +printable_list(L, _D, T, Enc) when T >= 0 -> +    case split(L, tsub(T, 2)) of +        {prefix, ""} -> +            false; +        {prefix, Prefix} when Enc =:= latin1 -> +            io_lib:printable_latin1_list(Prefix) andalso {true, Prefix}; +        {prefix, Prefix} -> +            %% Probably an overestimation. +            io_lib:printable_list(Prefix) andalso {true, Prefix}; +        all when Enc =:= latin1 -> +            io_lib:printable_latin1_list(L); +        all -> +            io_lib:printable_list(L) +    end; +printable_list(L, _D, T, _Uni) when T < 0->      io_lib:printable_list(L). -printable_bin(Bin, D, Enc) when D >= 0, ?CHARS * D =< byte_size(Bin) -> -    printable_bin(Bin, erlang:min(?CHARS * D, byte_size(Bin)), D, Enc); -printable_bin(Bin, D, Enc) -> -    printable_bin(Bin, byte_size(Bin), D, Enc). +split(L, N) -> +    try lists:split(N, L) of +        {_, []} -> +            all; +        {Prefix, _} -> +            {prefix, Prefix} +    catch _:_ -> all +    end. + +printable_bin0(Bin, D, T, Enc) -> +    Len = case D >= 0 of +              true -> +                  DChars = erlang:min(?CHARS * D, byte_size(Bin)), +                  case T >= 0 of +                      true -> +                          erlang:min(T, DChars); +                      false -> +                          DChars +                  end; +              false when T < 0 -> +                  byte_size(Bin); +              false when T >= 0 -> +                  T +          end, +    printable_bin(Bin, Len, D, Enc).  printable_bin(Bin, Len, D, latin1) ->      N = erlang:min(20, Len), @@ -689,28 +848,70 @@ write_string(S, latin1) ->  write_string(S, _Uni) ->      io_lib:write_string(S, $"). %" +expand({_, _, _Dots=0, no_more} = If, _T, _Dd) -> If; +%% expand({{list,L}, _Len, _, no_more}, T, Dd) -> +%%     {NL, NLen, NDots} = expand_list(L, T, Dd, 2), +%%     {{list,NL}, NLen, NDots, no_more}; +expand({{tuple,IsTagged,L}, _Len, _, no_more}, T, Dd) -> +    {NL, NLen, NDots} = expand_list(L, T, Dd, 2), +    {{tuple,IsTagged,NL}, NLen, NDots, no_more}; +expand({{map, Pairs}, _Len, _, no_more}, T, Dd) -> +    {NPairs, NLen, NDots} = expand_list(Pairs, T, Dd, 3), +    {{map, NPairs}, NLen, NDots, no_more}; +expand({{map_pair, K, V}, _Len, _, no_more}, T, Dd) -> +    {_, KL, KD, _} = P1 = expand(K, tsub(T, 1), Dd), +    KL1 = KL + 4, +    {_, VL, VD, _} = P2 = expand(V, tsub(T, KL1), Dd), +    {{map_pair, P1, P2}, KL1 + VL, KD + VD, no_more}; +expand({{record, [{Name,NameL} | L]}, _Len, _, no_more}, T, Dd) -> +    {NL, NLen, NDots} = expand_list(L, T, Dd, NameL + 2), +    {{record, [{Name,NameL} | NL]}, NLen, NDots, no_more}; +expand({{field, Name, NameL, Field}, _Len, _, no_more}, T, Dd) -> +    F = {_S, L, Dots, _} = expand(Field, tsub(T, NameL), Dd), +    {{field, Name, NameL, F}, NameL + L, Dots, no_more}; +expand({_, _, _, More}, T, Dd) -> +    More(T, Dd). + +expand_list(Ifs, T, Dd, L0) -> +    L = expand_list(Ifs, tsub(T, L0), Dd), +    {Len, Dots} = list_length(L, L0, 0), +    {L, Len, Dots}. + +expand_list([], _T, _Dd) -> +    []; +expand_list([If | Ifs], T, Dd) -> +    {_, Len1, _, _} = Elem1 = expand(If, tsub(T, 1), Dd), +    [Elem1 | expand_list(Ifs, tsub(T, Len1 + 1), Dd)]; +expand_list({_, _, _, More}, T, Dd) -> +    More(T, Dd). + +%% Make sure T does not change sign. +tsub(T, _) when T < 0 -> T; +tsub(T, E) when T >= E -> T - E; +tsub(_, _) -> 0. +  %% Throw 'no_good' if the indentation exceeds half the line length  %% unless there is room for M characters on the line. -cind({_S, Len}, Col, Ll, M, Ind, LD, W) when Len < Ll - Col - LD, -                                             Len + W + LD =< M -> +cind({_S, Len, _, _}, Col, Ll, M, Ind, LD, W) when Len < Ll - Col - LD, +                                                   Len + W + LD =< M ->      Ind; -cind({{list,L}, _Len}, Col, Ll, M, Ind, LD, W) -> +cind({{list,L}, _Len, _, _}, Col, Ll, M, Ind, LD, W) ->      cind_list(L, Col + 1, Ll, M, Ind, LD, W + 1); -cind({{tuple,true,L}, _Len}, Col, Ll, M, Ind, LD, W) -> +cind({{tuple,true,L}, _Len, _ ,_}, Col, Ll, M, Ind, LD, W) ->      cind_tag_tuple(L, Col, Ll, M, Ind, LD, W + 1); -cind({{tuple,false,L}, _Len}, Col, Ll, M, Ind, LD, W) -> +cind({{tuple,false,L}, _Len, _, _}, Col, Ll, M, Ind, LD, W) ->      cind_list(L, Col + 1, Ll, M, Ind, LD, W + 1); -cind({{map,Pairs},_Len}, Col, Ll, M, Ind, LD, W) -> +cind({{map,Pairs}, _Len, _, _}, Col, Ll, M, Ind, LD, W) ->      cind_map(Pairs, Col + 2, Ll, M, Ind, LD, W + 2); -cind({{record,[{_Name,NLen} | L]}, _Len}, Col, Ll, M, Ind, LD, W) -> +cind({{record,[{_Name,NLen} | L]}, _Len, _, _}, Col, Ll, M, Ind, LD, W) ->      cind_record(L, NLen, Col, Ll, M, Ind, LD, W + NLen + 1); -cind({{bin,_S}, _Len}, _Col, _Ll, _M, Ind, _LD, _W) -> +cind({{bin,_S}, _Len, _, _}, _Col, _Ll, _M, Ind, _LD, _W) ->      Ind; -cind({_S, _Len}, _Col, _Ll, _M, Ind, _LD, _W) -> +cind({_S,_Len,_,_}, _Col, _Ll, _M, Ind, _LD, _W) ->      Ind. -cind_tag_tuple([{_Tag,Tlen} | L], Col, Ll, M, Ind, LD, W) -> +cind_tag_tuple([{_Tag,Tlen,_,_} | L], Col, Ll, M, Ind, LD, W) ->      TagInd = Tlen + 2,      Tcol = Col + TagInd,      if @@ -732,9 +933,9 @@ cind_map([P | Ps], Col, Ll, M, Ind, LD, W) ->      PW = cind_pair(P, Col, Ll, M, Ind, last_depth(Ps, LD), W),      cind_pairs_tail(Ps, Col, Col + PW, Ll, M, Ind, LD, W + PW);  cind_map(_, _Col, _Ll, _M, Ind, _LD, _W) -> -    Ind. +    Ind.                                        % cannot happen -cind_pairs_tail([{_, Len}=P | Ps], Col0, Col, Ll, M, Ind, LD, W) -> +cind_pairs_tail([{_, Len, _, _} = P | Ps], Col0, Col, Ll, M, Ind, LD, W) ->      LD1 = last_depth(Ps, LD),      ELen = 1 + Len,      if @@ -748,7 +949,7 @@ cind_pairs_tail([{_, Len}=P | Ps], Col0, Col, Ll, M, Ind, LD, W) ->  cind_pairs_tail(_, _Col0, _Col, _Ll, _M, Ind, _LD, _W) ->      Ind. -cind_pair({{map_pair, _Key, _Value}, Len}=Pair, Col, Ll, M, _Ind, LD, W) +cind_pair({{map_pair, _Key, _Value}, Len, _, _}=Pair, Col, Ll, M, _Ind, LD, W)           when Len < Ll - Col - LD, Len + W + LD =< M ->      if          ?ATM_PAIR(Pair) -> @@ -756,7 +957,7 @@ cind_pair({{map_pair, _Key, _Value}, Len}=Pair, Col, Ll, M, _Ind, LD, W)          true ->              Ll      end; -cind_pair({{map_pair, K, V}, _Len}, Col0, Ll, M, Ind, LD, W0) -> +cind_pair({{map_pair, K, V}, _Len, _, _}, Col0, Ll, M, Ind, LD, W0) ->      cind(K, Col0, Ll, M, Ind, LD, W0),      I = map_value_indent(Ind),      cind(V, Col0 + I, Ll, M, Ind, LD, 0), @@ -778,7 +979,7 @@ cind_record([F | Fs], Nlen, Col0, Ll, M, Ind, LD, W0) ->  cind_record(_, _Nlen, _Col, _Ll, _M, Ind, _LD, _W) ->      Ind. -cind_fields_tail([{_, Len}=F | Fs], Col0, Col, Ll, M, Ind, LD, W) -> +cind_fields_tail([{_, Len, _, _} = F | Fs], Col0, Col, Ll, M, Ind, LD, W) ->      LD1 = last_depth(Fs, LD),      ELen = 1 + Len,      if @@ -792,7 +993,7 @@ cind_fields_tail([{_, Len}=F | Fs], Col0, Col, Ll, M, Ind, LD, W) ->  cind_fields_tail(_, _Col0, _Col, _Ll, _M, Ind, _LD, _W) ->      Ind. -cind_field({{field, _N, _NL, _F}, Len}=Fl, Col, Ll, M, _Ind, LD, W)  +cind_field({{field, _N, _NL, _F}, Len, _, _}=Fl, Col, Ll, M, _Ind, LD, W)           when Len < Ll - Col - LD, Len + W + LD =< M ->      if          ?ATM_FLD(Fl) -> @@ -800,7 +1001,7 @@ cind_field({{field, _N, _NL, _F}, Len}=Fl, Col, Ll, M, _Ind, LD, W)          true ->              Ll      end; -cind_field({{field, _Name, NameL, F}, _Len}, Col0, Ll, M, Ind, LD, W0) -> +cind_field({{field, _Name, NameL, F},_Len,_,_}, Col0, Ll, M, Ind, LD, W0) ->      {Col, W} = cind_rec(NameL, Col0, Ll, M, Ind, W0 + NameL),      cind(F, Col, Ll, M, Ind, LD, W),      Ll. @@ -823,7 +1024,7 @@ cind_rec(RInd, Col0, Ll, M, Ind, W0) ->              throw(no_good)      end. -cind_list({dots, _}, _Col0, _Ll, _M, Ind, _LD, _W) -> +cind_list({dots, _, _, _}, _Col0, _Ll, _M, Ind, _LD, _W) ->      Ind;  cind_list([E | Es], Col0, Ll, M, Ind, LD, W) ->      WE = cind_element(E, Col0, Ll, M, Ind, last_depth(Es, LD), W), @@ -831,7 +1032,7 @@ cind_list([E | Es], Col0, Ll, M, Ind, LD, W) ->  cind_tail([], _Col0, _Col, _Ll, _M, Ind, _LD, _W) ->      Ind; -cind_tail([{_, Len}=E | Es], Col0, Col, Ll, M, Ind, LD, W) -> +cind_tail([{_, Len, _, _} = E | Es], Col0, Col, Ll, M, Ind, LD, W) ->      LD1 = last_depth(Es, LD),      ELen = 1 + Len,      if  @@ -842,9 +1043,9 @@ cind_tail([{_, Len}=E | Es], Col0, Col, Ll, M, Ind, LD, W) ->              WE = cind_element(E, Col0, Ll, M, Ind, LD1, 0),              cind_tail(Es, Col0, Col0 + WE, Ll, M, Ind, LD, WE)      end; -cind_tail({dots, _}, _Col0, _Col, _Ll, _M, Ind, _LD, _W) -> +cind_tail({dots, _, _, _}, _Col0, _Col, _Ll, _M, Ind, _LD, _W) ->      Ind; -cind_tail({_, Len}=E, _Col0, Col, Ll, M, Ind, LD, W) +cind_tail({_, Len, _, _}=E, _Col0, Col, Ll, M, Ind, LD, W)                    when Len + 1 < Ll - Col - (LD + 1),                          Len + 1 + W + (LD + 1) =< M,                          ?ATM(E) -> @@ -852,7 +1053,7 @@ cind_tail({_, Len}=E, _Col0, Col, Ll, M, Ind, LD, W)  cind_tail(E, _Col0, Col, Ll, M, Ind, LD, _W) ->      cind(E, Col, Ll, M, Ind, LD + 1, 0). -cind_element({_, Len}=E, Col, Ll, M, _Ind, LD, W) +cind_element({_, Len, _, _}=E, Col, Ll, M, _Ind, LD, W)             when Len < Ll - Col - LD, Len + W + LD =< M, ?ATM(E) ->      Len;  cind_element(E, Col, Ll, M, Ind, LD, W) -> diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl index e4153e7899..1be37672e7 100644 --- a/lib/stdlib/src/shell.erl +++ b/lib/stdlib/src/shell.erl @@ -1416,7 +1416,7 @@ pp(V, I, D, RT) ->                  true          end,      io_lib_pretty:print(V, ([{column, I}, {line_length, columns()}, -                             {depth, D}, {max_chars, ?CHAR_MAX}, +                             {depth, D}, {line_max_chars, ?CHAR_MAX},                               {strings, Strings},                               {record_print_fun, record_print_fun(RT)}]                              ++ enc())). | 
