diff options
Diffstat (limited to 'lib/stdlib/src')
25 files changed, 1474 insertions, 743 deletions
diff --git a/lib/stdlib/src/Makefile b/lib/stdlib/src/Makefile index 8b156929d7..dc3735055a 100644 --- a/lib/stdlib/src/Makefile +++ b/lib/stdlib/src/Makefile @@ -238,6 +238,13 @@ $(EBIN)/erl_tar.beam: ../../kernel/include/file.hrl erl_tar.hrl $(EBIN)/file_sorter.beam: ../../kernel/include/file.hrl $(EBIN)/filelib.beam: ../../kernel/include/file.hrl $(EBIN)/filename.beam: ../../kernel/include/file.hrl +$(EBIN)/gen_event.beam: ../../kernel/include/logger.hrl +$(EBIN)/gen_fsm.beam: ../../kernel/include/logger.hrl +$(EBIN)/gen_server.beam: ../../kernel/include/logger.hrl +$(EBIN)/gen_statem.beam: ../../kernel/include/logger.hrl +$(EBIN)/proc_lib.beam: ../../kernel/include/logger.hrl $(EBIN)/qlc_pt.beam: ../include/ms_transform.hrl $(EBIN)/shell.beam: ../../kernel/include/file.hrl +$(EBIN)/supervisor.beam: ../../kernel/include/logger.hrl +$(EBIN)/supervisor_bridge.beam: ../../kernel/include/logger.hrl $(EBIN)/zip.beam: ../include/zip.hrl ../../kernel/include/file.hrl diff --git a/lib/stdlib/src/calendar.erl b/lib/stdlib/src/calendar.erl index 55a0cfc9a1..9a600c1972 100644 --- a/lib/stdlib/src/calendar.erl +++ b/lib/stdlib/src/calendar.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2016. 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. @@ -39,8 +39,14 @@ now_to_datetime/1, % = now_to_universal_time/1 now_to_local_time/1, now_to_universal_time/1, + rfc3339_to_system_time/1, + rfc3339_to_system_time/2, seconds_to_daystime/1, seconds_to_time/1, + system_time_to_local_time/2, + system_time_to_universal_time/2, + system_time_to_rfc3339/1, + system_time_to_rfc3339/2, time_difference/2, time_to_seconds/1, universal_time/0, @@ -55,10 +61,13 @@ -define(SECONDS_PER_DAY, 86400). -define(DAYS_PER_YEAR, 365). -define(DAYS_PER_LEAP_YEAR, 366). --define(DAYS_PER_4YEARS, 1461). --define(DAYS_PER_100YEARS, 36524). --define(DAYS_PER_400YEARS, 146097). +%% -define(DAYS_PER_4YEARS, 1461). +%% -define(DAYS_PER_100YEARS, 36524). +%% -define(DAYS_PER_400YEARS, 146097). -define(DAYS_FROM_0_TO_1970, 719528). +-define(DAYS_FROM_0_TO_10000, 2932897). +-define(SECONDS_FROM_0_TO_1970, (?DAYS_FROM_0_TO_1970*?SECONDS_PER_DAY)). +-define(SECONDS_FROM_0_TO_10000, (?DAYS_FROM_0_TO_10000*?SECONDS_PER_DAY)). %%---------------------------------------------------------------------- %% Types @@ -83,6 +92,13 @@ -type datetime1970() :: {{year1970(),month(),day()},time()}. -type yearweeknum() :: {year(),weeknum()}. +-type rfc3339_string() :: [byte(), ...]. +%% By design 'native' is not supported: +-type rfc3339_time_unit() :: 'microsecond' + | 'millisecond' + | 'nanosecond' + | 'second'. + %%---------------------------------------------------------------------- %% All dates are according the the Gregorian calendar. In this module @@ -309,8 +325,7 @@ local_time_to_universal_time_dst(DateTime) -> -spec now_to_datetime(Now) -> datetime1970() when Now :: erlang:timestamp(). now_to_datetime({MSec, Sec, _uSec}) -> - Sec0 = MSec*1000000 + Sec + ?DAYS_FROM_0_TO_1970*?SECONDS_PER_DAY, - gregorian_seconds_to_datetime(Sec0). + system_time_to_datetime(MSec*1000000 + Sec). -spec now_to_universal_time(Now) -> datetime1970() when Now :: erlang:timestamp(). @@ -328,6 +343,33 @@ now_to_local_time({MSec, Sec, _uSec}) -> erlang:universaltime_to_localtime( now_to_universal_time({MSec, Sec, _uSec})). +-spec rfc3339_to_system_time(DateTimeString) -> integer() when + DateTimeString :: rfc3339_string(). + +rfc3339_to_system_time(DateTimeString) -> + rfc3339_to_system_time(DateTimeString, []). + +-spec rfc3339_to_system_time(DateTimeString, Options) -> integer() when + DateTimeString :: rfc3339_string(), + Options :: [Option], + Option :: {'unit', rfc3339_time_unit()}. + +rfc3339_to_system_time(DateTimeString, Options) -> + Unit = proplists:get_value(unit, Options, second), + %% _T is the character separating the date and the time: + {DateStr, [_T|TimeStr]} = lists:split(10, DateTimeString), + {TimeStr2, TimeStr3} = lists:split(8, TimeStr), + {ok, [Hour, Min, Sec], []} = io_lib:fread("~d:~d:~d", TimeStr2), + {ok, [Year, Month, Day], []} = io_lib:fread("~d-~d-~d", DateStr), + DateTime = {{Year, Month, Day}, {Hour, Min, Sec}}, + IsFractionChar = fun(C) -> C >= $0 andalso C =< $9 orelse C =:= $. end, + {FractionStr, UtcOffset} = lists:splitwith(IsFractionChar, TimeStr3), + Time = datetime_to_system_time(DateTime), + Secs = Time - offset_adjustment(Time, second, UtcOffset), + check(DateTimeString, Options, Secs), + ScaledEpoch = erlang:convert_time_unit(Secs, second, Unit), + ScaledEpoch + copy_sign(fraction(Unit, FractionStr), ScaledEpoch). + %% seconds_to_daystime(Secs) = {Days, {Hour, Minute, Second}} @@ -363,6 +405,55 @@ seconds_to_time(Secs) when Secs >= 0, Secs < ?SECONDS_PER_DAY -> Second = Secs1 rem ?SECONDS_PER_MINUTE, {Hour, Minute, Second}. +-spec system_time_to_local_time(Time, TimeUnit) -> datetime() when + Time :: integer(), + TimeUnit :: erlang:time_unit(). + +system_time_to_local_time(Time, TimeUnit) -> + UniversalDate = system_time_to_universal_time(Time, TimeUnit), + erlang:universaltime_to_localtime(UniversalDate). + +-spec system_time_to_universal_time(Time, TimeUnit) -> datetime() when + Time :: integer(), + TimeUnit :: erlang:time_unit(). + +system_time_to_universal_time(Time, TimeUnit) -> + Secs = erlang:convert_time_unit(Time, TimeUnit, second), + system_time_to_datetime(Secs). + +-spec system_time_to_rfc3339(Time) -> DateTimeString when + Time :: integer(), + DateTimeString :: rfc3339_string(). + +system_time_to_rfc3339(Time) -> + system_time_to_rfc3339(Time, []). + +-type offset() :: [byte()] | (Time :: integer()). +-spec system_time_to_rfc3339(Time, Options) -> DateTimeString when + Time :: integer(), % Since Epoch + Options :: [Option], + Option :: {'offset', offset()} + | {'time_designator', byte()} + | {'unit', rfc3339_time_unit()}, + DateTimeString :: rfc3339_string(). + +system_time_to_rfc3339(Time, Options) -> + Unit = proplists:get_value(unit, Options, second), + OffsetOption = proplists:get_value(offset, Options, ""), + T = proplists:get_value(time_designator, Options, $T), + AdjustmentSecs = offset_adjustment(Time, Unit, OffsetOption), + Offset = offset(OffsetOption, AdjustmentSecs), + Adjustment = erlang:convert_time_unit(AdjustmentSecs, second, Unit), + AdjustedTime = Time + Adjustment, + Factor = factor(Unit), + Secs = AdjustedTime div Factor, + check(Time, Options, Secs), + DateTime = system_time_to_datetime(Secs), + {{Year, Month, Day}, {Hour, Min, Sec}} = DateTime, + FractionStr = fraction_str(Factor, AdjustedTime), + flat_fwrite("~4.10.0B-~2.10.0B-~2.10.0B~c~2.10.0B:~2.10.0B:~2.10.0B~s~s", + [Year, Month, Day, T, Hour, Min, Sec, FractionStr, Offset]). + %% time_difference(T1, T2) = Tdiff %% %% Returns the difference between two {Date, Time} structures. @@ -550,3 +641,85 @@ df(Year, _) -> true -> 1; false -> 0 end. + +check(_Arg, _Options, Secs) when Secs >= - ?SECONDS_FROM_0_TO_1970, + Secs < ?SECONDS_FROM_0_TO_10000 -> + ok; +check(Arg, Options, _Secs) -> + erlang:error({badarg, [Arg, Options]}). + +datetime_to_system_time(DateTime) -> + datetime_to_gregorian_seconds(DateTime) - ?SECONDS_FROM_0_TO_1970. + +system_time_to_datetime(Seconds) -> + gregorian_seconds_to_datetime(Seconds + ?SECONDS_FROM_0_TO_1970). + +offset(OffsetOption, Secs0) when OffsetOption =:= ""; + is_integer(OffsetOption) -> + Sign = case Secs0 < 0 of + true -> $-; + false -> $+ + end, + Secs = abs(Secs0), + Hour = Secs div 3600, + Min = (Secs rem 3600) div 60, + io_lib:fwrite("~c~2.10.0B:~2.10.0B", [Sign, Hour, Min]); +offset(OffsetOption, _Secs) -> + OffsetOption. + +offset_adjustment(Time, Unit, OffsetString) when is_list(OffsetString) -> + offset_string_adjustment(Time, Unit, OffsetString); +offset_adjustment(_Time, Unit, Offset) when is_integer(Offset) -> + erlang:convert_time_unit(Offset, Unit, second). + +offset_string_adjustment(Time, Unit, "") -> + local_offset(Time, Unit); +offset_string_adjustment(_Time, _Unit, "Z") -> + 0; +offset_string_adjustment(_Time, _Unit, "z") -> + 0; +offset_string_adjustment(_Time, _Unit, [Sign|Tz]) -> + {ok, [Hour, Min], []} = io_lib:fread("~d:~d", Tz), + Adjustment = 3600 * Hour + 60 * Min, + case Sign of + $- -> -Adjustment; + $+ -> Adjustment + end. + +local_offset(SystemTime, Unit) -> + LocalTime = system_time_to_local_time(SystemTime, Unit), + UniversalTime = system_time_to_universal_time(SystemTime, Unit), + LocalSecs = datetime_to_gregorian_seconds(LocalTime), + UniversalSecs = datetime_to_gregorian_seconds(UniversalTime), + LocalSecs - UniversalSecs. + +fraction_str(Factor, Time) -> + case Time rem Factor of + 0 -> + ""; + Fraction -> + FS = io_lib:fwrite(".~*..0B", [log10(Factor), abs(Fraction)]), + string:trim(FS, trailing, "0") + end. + +fraction(second, _) -> + 0; +fraction(_, "") -> + 0; +fraction(Unit, FractionStr) -> + round(factor(Unit) * list_to_float([$0|FractionStr])). + +copy_sign(N1, N2) when N2 < 0 -> -N1; +copy_sign(N1, _N2) -> N1. + +factor(second) -> 1; +factor(millisecond) -> 1000; +factor(microsecond) -> 1000000; +factor(nanosecond) -> 1000000000. + +log10(1000) -> 3; +log10(1000000) -> 6; +log10(1000000000) -> 9. + +flat_fwrite(F, S) -> + lists:flatten(io_lib:fwrite(F, S)). diff --git a/lib/stdlib/src/erl_internal.erl b/lib/stdlib/src/erl_internal.erl index 89b97b901e..6d3d5baa23 100644 --- a/lib/stdlib/src/erl_internal.erl +++ b/lib/stdlib/src/erl_internal.erl @@ -76,6 +76,7 @@ guard_bif(floor, 1) -> true; guard_bif(hd, 1) -> true; guard_bif(length, 1) -> true; guard_bif(map_size, 1) -> true; +guard_bif(map_get, 2) -> true; guard_bif(node, 0) -> true; guard_bif(node, 1) -> true; guard_bif(round, 1) -> true; @@ -337,6 +338,7 @@ bif(list_to_tuple, 1) -> true; bif(load_module, 2) -> true; bif(make_ref, 0) -> true; bif(map_size,1) -> true; +bif(map_get,2) -> true; bif(max,2) -> true; bif(min,2) -> true; bif(module_loaded, 1) -> true; diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 9a62d21d34..e9ac2fcdff 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -2,7 +2,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. @@ -93,13 +93,6 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) -> }). -%% Are we outside or inside a catch or try/catch? --type catch_scope() :: 'none' - | 'after_old_catch' - | 'after_try' - | 'wrong_part_of_try' - | 'try_catch'. - %% Define the lint state record. %% 'called' and 'exports' contain {Line, {Function, Arity}}, %% the other function collections contain {Function, Arity}. @@ -144,9 +137,7 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) -> :: dict:dict(ta(), #typeinfo{}), exp_types=gb_sets:empty() %Exported types :: gb_sets:set(ta()), - in_try_head=false :: boolean(), %In a try head. - catch_scope = none %Inside/outside try or catch - :: catch_scope() + in_try_head=false :: boolean() %In a try head. }). -type lint_state() :: #lint{}. @@ -233,15 +224,6 @@ format_error({redefine_old_bif_import,{F,A}}) -> format_error({redefine_bif_import,{F,A}}) -> io_lib:format("import directive overrides auto-imported BIF ~w/~w~n" " - use \"-compile({no_auto_import,[~w/~w]}).\" to resolve name clash", [F,A,F,A]); -format_error({get_stacktrace,wrong_part_of_try}) -> - "erlang:get_stacktrace/0 used in the wrong part of 'try' expression. " - "(Use it in the block between 'catch' and 'end'.)"; -format_error({get_stacktrace,after_old_catch}) -> - "erlang:get_stacktrace/0 used following an old-style 'catch' " - "may stop working in a future release. (Use it inside 'try'.)"; -format_error({get_stacktrace,after_try}) -> - "erlang:get_stacktrace/0 used following a 'try' expression " - "may stop working in a future release. (Use it inside 'try'.)"; format_error({deprecated, MFA, ReplacementMFA, Rel}) -> io_lib:format("~s is deprecated and will be removed in ~s; use ~s", [format_mfa(MFA), Rel, format_mfa(ReplacementMFA)]); @@ -591,10 +573,7 @@ start(File, Opts) -> false, Opts)}, {missing_spec_all, bool_option(warn_missing_spec_all, nowarn_missing_spec_all, - false, Opts)}, - {get_stacktrace, - bool_option(warn_get_stacktrace, nowarn_get_stacktrace, - true, Opts)} + false, Opts)} ], Enabled1 = [Category || {Category,true} <- Enabled0], Enabled = ordsets:from_list(Enabled1), @@ -1426,7 +1405,7 @@ call_function(Line, F, A, #lint{usage=Usage0,called=Cd,func=Func,file=File}=St) %% function(Line, Name, Arity, Clauses, State) -> State. function(Line, Name, Arity, Cs, St0) -> - St1 = St0#lint{func={Name,Arity},catch_scope=none}, + St1 = St0#lint{func={Name,Arity}}, St2 = define_function(Line, Name, Arity, St1), clauses(Cs, St2). @@ -2116,6 +2095,10 @@ is_gexpr({cons,_L,H,T}, Info) -> is_gexpr_list([H,T], Info); is_gexpr({tuple,_L,Es}, Info) -> is_gexpr_list(Es, Info); %%is_gexpr({struct,_L,_Tag,Es}, Info) -> %% is_gexpr_list(Es, Info); +is_gexpr({map,_L,Es}, Info) -> + is_map_fields(Es, Info); +is_gexpr({map,_L,Src,Es}, Info) -> + is_gexpr(Src, Info) andalso is_map_fields(Es, Info); is_gexpr({record_index,_L,_Name,Field}, Info) -> is_gexpr(Field, Info); is_gexpr({record_field,_L,Rec,_Name,Field}, Info) -> @@ -2158,6 +2141,14 @@ is_gexpr_op(Op, A) -> is_gexpr_list(Es, Info) -> all(fun (E) -> is_gexpr(E, Info) end, Es). +is_map_fields([{Tag,_,K,V}|Fs], Info) when Tag =:= map_field_assoc; + Tag =:= map_field_exact -> + is_gexpr(K, Info) andalso + is_gexpr(V, Info) andalso + is_map_fields(Fs, Info); +is_map_fields([], _Info) -> true; +is_map_fields(_T, _Info) -> false. + is_gexpr_fields(Fs, L, Name, {RDs,_}=Info) -> IFs = case dict:find(Name, RDs) of {ok,{_Line,Fields}} -> Fs ++ init_fields(Fs, L, Fields); @@ -2367,7 +2358,7 @@ expr({call,Line,F,As}, Vt, St0) -> expr({'try',Line,Es,Scs,Ccs,As}, Vt, St0) -> %% Currently, we don't allow any exports because later %% passes cannot handle exports in combination with 'after'. - {Evt0,St1} = exprs(Es, Vt, St0#lint{catch_scope=wrong_part_of_try}), + {Evt0,St1} = exprs(Es, Vt, St0), TryLine = {'try',Line}, Uvt = vtunsafe(TryLine, Evt0, Vt), Evt1 = vtupdate(Uvt, Evt0), @@ -2379,12 +2370,11 @@ expr({'try',Line,Es,Scs,Ccs,As}, Vt, St0) -> {Avt0,St} = exprs(As, vtupdate(Evt2, Vt), St2), Avt1 = vtupdate(vtunsafe(TryLine, Avt0, Vt), Avt0), Avt = vtmerge(Evt2, Avt1), - {Avt,St#lint{catch_scope=after_try}}; + {Avt,St}; expr({'catch',Line,E}, Vt, St0) -> %% No new variables added, flag new variables as unsafe. {Evt,St} = expr(E, Vt, St0), - {vtupdate(vtunsafe({'catch',Line}, Evt, Vt), Evt), - St#lint{catch_scope=after_old_catch}}; + {vtupdate(vtunsafe({'catch',Line}, Evt, Vt), Evt),St}; expr({match,_Line,P,E}, Vt, St0) -> {Evt,St1} = expr(E, Vt, St0), {Pvt,Bvt,St2} = pattern(P, vtupdate(Evt, Vt), St1), @@ -3223,7 +3213,7 @@ is_module_dialyzer_option(Option) -> try_clauses(Scs, Ccs, In, Vt, St0) -> {Csvt0,St1} = icrt_clauses(Scs, Vt, St0), - St2 = St1#lint{catch_scope=try_catch,in_try_head=true}, + St2 = St1#lint{in_try_head=true}, {Csvt1,St3} = icrt_clauses(Ccs, Vt, St2), Csvt = Csvt0 ++ Csvt1, UpdVt = icrt_export(Csvt, Vt, In, St3), @@ -3243,7 +3233,7 @@ 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, #lint{catch_scope=Scope}=St0) -> +icrt_clause({clause,_Line,H,G,B}, Vt0, St0) -> Vt1 = taint_stack_var(Vt0, H, St0), {Hvt,Binvt,St1} = head(H, Vt1, St0), Vt2 = vtupdate(Hvt, Binvt), @@ -3251,7 +3241,7 @@ icrt_clause({clause,_Line,H,G,B}, Vt0, #lint{catch_scope=Scope}=St0) -> {Gvt,St2} = guard(G, vtupdate(Vt3, Vt0), St1#lint{in_try_head=false}), Vt4 = vtupdate(Gvt, Vt2), {Bvt,St3} = exprs(B, vtupdate(Vt4, Vt0), St2), - {vtupdate(Bvt, Vt4),St3#lint{catch_scope=Scope}}. + {vtupdate(Bvt, Vt4),St3}. taint_stack_var(Vt, Pat, #lint{in_try_head=true}) -> [{tuple,_,[_,_,{var,_,Stk}]}] = Pat, @@ -3736,8 +3726,7 @@ has_wildcard_field([]) -> false. check_remote_function(Line, M, F, As, St0) -> St1 = deprecated_function(Line, M, F, As, St0), St2 = check_qlc_hrl(Line, M, F, As, St1), - St3 = check_get_stacktrace(Line, M, F, As, St2), - format_function(Line, M, F, As, St3). + format_function(Line, M, F, As, St2). %% check_qlc_hrl(Line, ModName, FuncName, [Arg], State) -> State %% Add warning if qlc:q/1,2 has been called but qlc.hrl has not @@ -3786,23 +3775,6 @@ deprecated_function(Line, M, F, As, St) -> St end. -check_get_stacktrace(Line, erlang, get_stacktrace, [], St) -> - case St of - #lint{catch_scope=none} -> - St; - #lint{catch_scope=try_catch} -> - St; - #lint{catch_scope=Scope} -> - case is_warn_enabled(get_stacktrace, St) of - false -> - St; - true -> - add_warning(Line, {get_stacktrace,Scope}, St) - end - end; -check_get_stacktrace(_, _, _, _, St) -> - St. - -dialyzer({no_match, deprecated_type/5}). deprecated_type(L, M, N, As, St) -> diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl index 14ca24362e..0c338b5952 100644 --- a/lib/stdlib/src/erl_parse.yrl +++ b/lib/stdlib/src/erl_parse.yrl @@ -1377,6 +1377,8 @@ normalise({map,_,Pairs}=M) -> ({map_field_assoc,_,K,V}) -> {normalise(K),normalise(V)}; (_) -> erlang:error({badarg,M}) end, Pairs)); +normalise({'fun',_,{function,{atom,_,M},{atom,_,F},{integer,_,A}}}) -> + fun M:F/A; %% Special case for unary +/-. normalise({op,_,'+',{char,_,I}}) -> I; normalise({op,_,'+',{integer,_,I}}) -> I; diff --git a/lib/stdlib/src/erl_posix_msg.erl b/lib/stdlib/src/erl_posix_msg.erl index bfafca1ff7..8959fea498 100644 --- a/lib/stdlib/src/erl_posix_msg.erl +++ b/lib/stdlib/src/erl_posix_msg.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1997-2016. All Rights Reserved. +%% Copyright Ericsson AB 1997-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. @@ -64,6 +64,7 @@ message_1(eduppkg) -> <<"duplicate package name">>; message_1(eexist) -> <<"file already exists">>; message_1(efault) -> <<"bad address in system call argument">>; message_1(efbig) -> <<"file too large">>; +message_1(eftype) -> <<"EFTYPE">>; message_1(ehostdown) -> <<"host is down">>; message_1(ehostunreach) -> <<"host is unreachable">>; message_1(eidrm) -> <<"identifier removed">>; @@ -115,6 +116,7 @@ message_1(enopkg) -> <<"package not installed">>; message_1(enoprotoopt) -> <<"bad proocol option">>; message_1(enospc) -> <<"no space left on device">>; message_1(enosr) -> <<"out of stream resources or not a stream device">>; +message_1(enostr) -> <<"not a stream">>; message_1(enosym) -> <<"unresolved symbol name">>; message_1(enosys) -> <<"function not implemented">>; message_1(enotblk) -> <<"block device required">>; @@ -128,6 +130,7 @@ message_1(enotty) -> <<"inappropriate device for ioctl">>; message_1(enotuniq) -> <<"name not unique on network">>; message_1(enxio) -> <<"no such device or address">>; message_1(eopnotsupp) -> <<"operation not supported on socket">>; +message_1(eoverflow) -> <<"offset too large for file system">>; message_1(eperm) -> <<"not owner">>; message_1(epfnosupport) -> <<"protocol family not supported">>; message_1(epipe) -> <<"broken pipe">>; @@ -167,4 +170,6 @@ message_1(ewouldblock) -> <<"operation would block">>; message_1(exdev) -> <<"cross-domain link">>; message_1(exfull) -> <<"message tables full">>; message_1(nxdomain) -> <<"non-existing domain">>; +message_1(exbadport) -> <<"inet_drv bad port state">>; +message_1(exbadseq) -> <<"inet_drv bad request sequence">>; message_1(_) -> <<"unknown POSIX error">>. diff --git a/lib/stdlib/src/gen_event.erl b/lib/stdlib/src/gen_event.erl index 73e4457bd0..53042251cc 100644 --- a/lib/stdlib/src/gen_event.erl +++ b/lib/stdlib/src/gen_event.erl @@ -47,16 +47,19 @@ system_replace_state/2, format_status/2]). +%% logger callback +-export([format_log/1]). + -export_type([handler/0, handler_args/0, add_handler_ret/0, del_handler_ret/0]). --import(error_logger, [error_msg/2]). - -record(handler, {module :: atom(), id = false, state, supervised = false :: 'false' | pid()}). +-include("logger.hrl"). + %%%========================================================================= %%% API %%%========================================================================= @@ -583,9 +586,13 @@ server_update(Handler1, Func, Event, SName) -> remove, SName, normal), no; {'EXIT', {undef, [{Mod1, handle_info, [_,_], _}|_]}} -> - error_logger:warning_msg("** Undefined handle_info in ~tp~n" - "** Unhandled message: ~tp~n", [Mod1, Event]), - {ok, Handler1}; + ?LOG_WARNING(#{label=>{gen_event,no_handle_info}, + module=>Mod1, + message=>Event}, + #{domain=>[beam,erlang,otp], + report_cb=>fun gen_event:format_log/1, + error_logger=>#{tag=>warning_msg}}), % warningmap?? + {ok, Handler1}; Other -> do_terminate(Mod1, Handler1, {error, Other}, State, Event, SName, crash), @@ -737,6 +744,23 @@ report_error(_Handler, normal, _, _, _) -> ok; report_error(_Handler, shutdown, _, _, _) -> ok; report_error(_Handler, {swapped,_,_}, _, _, _) -> ok; report_error(Handler, Reason, State, LastIn, SName) -> + ?LOG_ERROR(#{label=>{gen_event,terminate}, + handler=>handler(Handler), + name=>SName, + last_message=>LastIn, + state=>format_status(terminate,Handler#handler.module, + get(),State), + reason=>Reason}, + #{domain=>[beam,erlang,otp], + report_cb=>fun gen_event:format_log/1, + error_logger=>#{tag=>error}}). + +format_log(#{label:={gen_event,terminate}, + handler:=Handler, + name:=SName, + last_message:=LastIn, + state:=State, + reason:=Reason}) -> Reason1 = case Reason of {'EXIT',{undef,[{M,F,A,L}|MFAs]}} -> @@ -756,23 +780,18 @@ report_error(Handler, Reason, State, LastIn, SName) -> _ -> Reason end, - Mod = Handler#handler.module, - FmtState = case erlang:function_exported(Mod, format_status, 2) of - true -> - Args = [get(), State], - case catch Mod:format_status(terminate, Args) of - {'EXIT', _} -> State; - Else -> Else - end; - _ -> - State - end, - error_msg("** gen_event handler ~p crashed.~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]). + {"** gen_event handler ~p crashed.~n" + "** Was installed in ~tp~n" + "** Last event was: ~tp~n" + "** When handler state == ~tp~n" + "** Reason == ~tp~n", + [Handler,SName,LastIn,State,Reason1]}; +format_log(#{label:={gen_event,no_handle_info}, + module:=Mod, + message:=Msg}) -> + {"** Undefined handle_info in ~tp~n" + "** Unhandled message: ~tp~n", + [Mod, Msg]}. handler(Handler) when not Handler#handler.id -> Handler#handler.module; @@ -805,17 +824,21 @@ format_status(Opt, StatusData) -> [PDict, SysState, Parent, _Debug, [ServerName, MSL, _HibernateAfterTimeout, _Hib]] = StatusData, Header = gen:format_status_header("Status for event handler", ServerName), - FmtMSL = [case erlang:function_exported(Mod, format_status, 2) of - true -> - Args = [PDict, State], - case catch Mod:format_status(Opt, Args) of - {'EXIT', _} -> MSL; - Else -> MS#handler{state = Else} - end; - _ -> - MS - end || #handler{module = Mod, state = State} = MS <- MSL], + FmtMSL = [MS#handler{state=format_status(Opt, Mod, PDict, State)} + || #handler{module = Mod, state = State} = MS <- MSL], [{header, Header}, {data, [{"Status", SysState}, {"Parent", Parent}]}, {items, {"Installed handlers", FmtMSL}}]. + +format_status(Opt, Mod, PDict, State) -> + case erlang:function_exported(Mod, format_status, 2) of + true -> + Args = [PDict, State], + case catch Mod:format_status(Opt, Args) of + {'EXIT', _} -> State; + Else -> Else + end; + false -> + State + end. diff --git a/lib/stdlib/src/gen_fsm.erl b/lib/stdlib/src/gen_fsm.erl index 8c7db65563..77826c3dc6 100644 --- a/lib/stdlib/src/gen_fsm.erl +++ b/lib/stdlib/src/gen_fsm.erl @@ -105,6 +105,8 @@ %%% %%% --------------------------------------------------- +-include("logger.hrl"). + -export([start/3, start/4, start_link/3, start_link/4, stop/1, stop/3, @@ -124,6 +126,9 @@ system_replace_state/2, format_status/2]). +%% logger callback +-export([format_log/1]). + -deprecated({start, 3, next_major_release}). -deprecated({start, 4, next_major_release}). -deprecated({start_link, 3, next_major_release}). @@ -144,8 +149,6 @@ -deprecated({enter_loop, 5, next_major_release}). -deprecated({enter_loop, 6, next_major_release}). --import(error_logger, [format/2]). - %%% --------------------------------------------------- %%% Interface functions. %%% --------------------------------------------------- @@ -499,8 +502,12 @@ handle_msg(Msg, Parent, Name, StateName, StateData, Mod, _Time, HibernateAfterTi reply(From, Reply), exit(R); {'EXIT', {undef, [{Mod, handle_info, [_,_,_], _}|_]}} -> - error_logger:warning_msg("** Undefined handle_info in ~p~n" - "** Unhandled message: ~tp~n", [Mod, Msg]), + ?LOG_WARNING(#{label=>{gen_fsm,no_handle_info}, + module=>Mod, + message=>Msg}, + #{domain=>[beam,erlang,otp], + report_cb=>fun gen_fsm:format_log/1, + error_logger=>#{tag=>warning_msg}}), loop(Parent, Name, StateName, StateData, Mod, infinity, HibernateAfterTimeout, []); {'EXIT', What} -> terminate(What, Name, Msg, Mod, StateName, StateData, []); @@ -603,6 +610,24 @@ terminate(Reason, Name, Msg, Mod, StateName, StateData, Debug) -> end. error_info(Reason, Name, Msg, StateName, StateData, Debug) -> + ?LOG_ERROR(#{label=>{gen_fsm,terminate}, + name=>Name, + last_message=>Msg, + state_name=>StateName, + state_data=>StateData, + reason=>Reason}, + #{domain=>[beam,erlang,otp], + report_cb=>fun gen_fsm:format_log/1, + error_logger=>#{tag=>error}}), + sys:print_log(Debug), + ok. + +format_log(#{label:={gen_fsm,terminate}, + name:=Name, + last_message:=Msg, + state_name:=StateName, + state_data:=StateData, + reason:=Reason}) -> Reason1 = case Reason of {undef,[{M,F,A,L}|MFAs]} -> @@ -620,14 +645,18 @@ error_info(Reason, Name, Msg, StateName, StateData, Debug) -> _ -> Reason end, - Str = "** State machine ~tp terminating \n" ++ - get_msg_str(Msg) ++ - "** 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. + {"** State machine ~tp terminating \n" ++ + get_msg_str(Msg) ++ + "** When State == ~tp~n" + "** Data == ~tp~n" + "** Reason for termination = ~n** ~tp~n", + [Name, get_msg(Msg), StateName, StateData, Reason1]}; +format_log(#{label:={gen_fsm,no_handle_info}, + module:=Mod, + message:=Msg}) -> + {"** Undefined handle_info in ~p~n" + "** Unhandled message: ~tp~n", + [Mod, Msg]}. get_msg_str({'$gen_event', _Event}) -> "** Last event in was ~tp~n"; diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl index f29314d0a2..f65ef78636 100644 --- a/lib/stdlib/src/gen_server.erl +++ b/lib/stdlib/src/gen_server.erl @@ -104,9 +104,14 @@ system_replace_state/2, format_status/2]). +%% logger callback +-export([format_log/1]). + %% Internal exports -export([init_it/6]). +-include("logger.hrl"). + -define( STACKTRACE(), element(2, erlang:process_info(self(), current_stacktrace))). @@ -636,9 +641,13 @@ try_dispatch(Mod, Func, Msg, State) -> error:undef = R:Stacktrace when Func == handle_info -> case erlang:function_exported(Mod, handle_info, 2) of false -> - error_logger:warning_msg("** Undefined handle_info in ~p~n" - "** Unhandled message: ~tp~n", - [Mod, Msg]), + ?LOG_WARNING( + #{label=>{gen_server,no_handle_info}, + module=>Mod, + message=>Msg}, + #{domain=>[beam,erlang,otp], + report_cb=>fun gen_server:format_log/1, + error_logger=>#{tag=>warning_msg}}), {ok, {noreply, State}}; true -> {'EXIT', error, R, Stacktrace} @@ -849,8 +858,7 @@ terminate(Class, Reason, Stacktrace, ReportReason, Name, From, Msg, Mod, State, Reply = try_terminate(Mod, terminate_reason(Class, Reason, Stacktrace), State), case Reply of {'EXIT', C, R, S} -> - FmtState = format_status(terminate, Mod, get(), State), - error_info({R, S}, Name, From, Msg, FmtState, Debug), + error_info({R, S}, Name, From, Msg, Mod, State, Debug), erlang:raise(C, R, S); _ -> case {Class, Reason} of @@ -858,8 +866,7 @@ terminate(Class, Reason, Stacktrace, ReportReason, Name, From, Msg, Mod, State, {exit, shutdown} -> ok; {exit, {shutdown,_}} -> ok; _ -> - FmtState = format_status(terminate, Mod, get(), State), - error_info(ReportReason, Name, From, Msg, FmtState, Debug) + error_info(ReportReason, Name, From, Msg, Mod, State, Debug) end end, case Stacktrace of @@ -872,12 +879,46 @@ terminate(Class, Reason, Stacktrace, ReportReason, Name, From, Msg, Mod, State, terminate_reason(error, Reason, Stacktrace) -> {Reason, Stacktrace}; terminate_reason(exit, Reason, _Stacktrace) -> Reason. -error_info(_Reason, application_controller, _From, _Msg, _State, _Debug) -> +error_info(_Reason, application_controller, _From, _Msg, _Mod, _State, _Debug) -> %% OTP-5811 Don't send an error report if it's the system process %% application_controller which is terminating - let init take care %% of it instead ok; -error_info(Reason, Name, From, Msg, State, Debug) -> +error_info(Reason, Name, From, Msg, Mod, State, Debug) -> + ?LOG_ERROR(#{label=>{gen_server,terminate}, + name=>Name, + last_message=>Msg, + state=>format_status(terminate, Mod, get(), State), + reason=>Reason, + client_info=>client_stacktrace(From)}, + #{domain=>[beam,erlang,otp], + report_cb=>fun gen_server:format_log/1, + error_logger=>#{tag=>error}}), + sys:print_log(Debug), + ok. + +client_stacktrace(undefined) -> + undefined; +client_stacktrace({From,_Tag}) -> + client_stacktrace(From); +client_stacktrace(From) when is_pid(From), node(From) =:= node() -> + case process_info(From, [current_stacktrace, registered_name]) of + undefined -> + {From,dead}; + [{current_stacktrace, Stacktrace}, {registered_name, []}] -> + {From,{From,Stacktrace}}; + [{current_stacktrace, Stacktrace}, {registered_name, Name}] -> + {From,{Name,Stacktrace}} + end; +client_stacktrace(From) when is_pid(From) -> + {From,remote}. + +format_log(#{label:={gen_server,terminate}, + name:=Name, + last_message:=Msg, + state:=State, + reason:=Reason, + client_info:=Client}) -> Reason1 = case Reason of {undef,[{M,F,A,L}|MFAs]} -> @@ -893,36 +934,31 @@ error_info(Reason, Name, From, Msg, State, Debug) -> end end; _ -> - error_logger:limit_term(Reason) + logger:limit_term(Reason) end, - {ClientFmt, ClientArgs} = client_stacktrace(From), - LimitedState = error_logger:limit_term(State), - 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. -client_stacktrace(undefined) -> + {ClientFmt,ClientArgs} = format_client_log(Client), + {"** 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, logger:limit_term(State), Reason1] ++ ClientArgs}; +format_log(#{label:={gen_server,no_handle_info}, + module:=Mod, + message:=Msg}) -> + {"** Undefined handle_info in ~p~n" + "** Unhandled message: ~tp~n", + [Mod, Msg]}. + +format_client_log(undefined) -> {"", []}; -client_stacktrace({From, _Tag}) -> - client_stacktrace(From); -client_stacktrace(From) when is_pid(From), node(From) =:= node() -> - case process_info(From, [current_stacktrace, registered_name]) of - undefined -> - {"** Client ~p is dead~n", [From]}; - [{current_stacktrace, Stacktrace}, {registered_name, []}] -> - {"** Client ~p stacktrace~n" - "** ~tp~n", - [From, Stacktrace]}; - [{current_stacktrace, Stacktrace}, {registered_name, Name}] -> - {"** Client ~tp stacktrace~n" - "** ~tp~n", - [Name, Stacktrace]} - end; -client_stacktrace(From) when is_pid(From) -> - {"** Client ~p is remote on node ~p~n", [From, node(From)]}. +format_client_log({From,dead}) -> + {"** Client ~p is dead~n", [From]}; +format_client_log({From,remote}) -> + {"** Client ~p is remote on node ~p~n", [From, node(From)]}; +format_client_log({_From,{Name,Stacktrace}}) -> + {"** Client ~tp stacktrace~n" + "** ~tp~n", + [Name, Stacktrace]}. %%----------------------------------------------------------------- %% Status information diff --git a/lib/stdlib/src/gen_statem.erl b/lib/stdlib/src/gen_statem.erl index 9dc360a289..f558f0d33e 100644 --- a/lib/stdlib/src/gen_statem.erl +++ b/lib/stdlib/src/gen_statem.erl @@ -19,6 +19,8 @@ %% -module(gen_statem). +-include("logger.hrl"). + %% API -export( [start/3,start/4,start_link/3,start_link/4, @@ -44,6 +46,9 @@ -export( [wakeup_from_hibernate/3]). +%% logger callback +-export([format_log/1]). + %% Type exports for templates and callback modules -export_type( [event_type/0, @@ -143,7 +148,7 @@ timeout_action() | reply_action(). -type timeout_action() :: - (Timeout :: event_timeout()) | % {timeout,Timeout} + (Time :: event_timeout()) | % {timeout,Time,Time} {'timeout', % Set the event_timeout option Time :: event_timeout(), EventContent :: term()} | {'timeout', % Set the event_timeout option @@ -327,7 +332,8 @@ %% Type validation functions -compile( {inline, - [callback_mode/1, state_enter/1, from/1, event_type/1]}). + [callback_mode/1, state_enter/1, + event_type/1, from/1, timeout_event_type/1]}). %% callback_mode(CallbackMode) -> case CallbackMode of @@ -344,23 +350,26 @@ state_enter(StateEnter) -> false end. %% -from({Pid,_}) when is_pid(Pid) -> true; -from(_) -> false. -%% -event_type({call,From}) -> - from(From); event_type(Type) -> case Type of {call,From} -> from(From); + %% cast -> true; info -> true; - timeout -> true; - state_timeout -> true; internal -> true; - {timeout,_} -> true; - _ -> false + _ -> timeout_event_type(Type) + end. +%% +from({Pid,_}) when is_pid(Pid) -> true; +from(_) -> false. +%% +timeout_event_type(Type) -> + case Type of + timeout -> true; + state_timeout -> true; + {timeout,_Name} -> true; + _ -> false end. - -define( @@ -669,9 +678,9 @@ enter(Module, Opts, State, Data, Server, Actions, Parent) -> NewDebug = ?sys_debug(Debug, {Name,State}, {enter,Event,State}), case call_callback_mode(S) of #state{} = NewS -> - loop_event_actions( + loop_event_actions_list( Parent, NewDebug, NewS, - Events, Event, State, Data, #trans_opts{}, + Events, Event, State, Data, false, NewActions, CallEnter); [Class,Reason,Stacktrace] -> terminate( @@ -698,7 +707,7 @@ init_it(Starter, Parent, ServerRef, Module, Args, Opts) -> error_info( Class, Reason, Stacktrace, #state{name = Name}, - [], undefined), + []), erlang:raise(Class, Reason, Stacktrace) end. @@ -729,7 +738,7 @@ init_result(Starter, Parent, ServerRef, Module, Result, Opts) -> error_info( error, Error, ?STACKTRACE(), #state{name = Name}, - [], undefined), + []), exit(Error) end. @@ -1056,6 +1065,15 @@ loop_event_result( Parent, Debug, S, Events, Event, NextState, NewData, TransOpts, [], true); + {next_state,_NextState,_NewData} -> + terminate( + error, + {bad_state_enter_return_from_state_function,Result}, + ?STACKTRACE(), Debug, + S#state{ + state = State, data = Data, + hibernate = hibernate_in_trans_opts(TransOpts)}, + [Event|Events]); {next_state,State,NewData,Actions} -> loop_event_actions( Parent, Debug, S, @@ -1067,6 +1085,15 @@ loop_event_result( Parent, Debug, S, Events, Event, NextState, NewData, TransOpts, Actions, true); + {next_state,_NextState,_NewData,_Actions} -> + terminate( + error, + {bad_state_enter_return_from_state_function,Result}, + ?STACKTRACE(), Debug, + S#state{ + state = State, data = Data, + hibernate = hibernate_in_trans_opts(TransOpts)}, + [Event|Events]); %% {keep_state,NewData} -> loop_event_actions( @@ -1160,12 +1187,6 @@ loop_event_result( [Event|Events]) end. --compile({inline, [hibernate_in_trans_opts/1]}). -hibernate_in_trans_opts(false) -> - (#trans_opts{})#trans_opts.hibernate; -hibernate_in_trans_opts(#trans_opts{hibernate = Hibernate}) -> - Hibernate. - %% Ensure that Actions are a list loop_event_actions( Parent, Debug, S, @@ -1198,10 +1219,16 @@ loop_event_actions_list( S#state{ state = NextState, data = NewerData, - hibernate = TransOpts#trans_opts.hibernate}, + hibernate = hibernate_in_trans_opts(TransOpts)}, [Event|Events]) end. +-compile({inline, [hibernate_in_trans_opts/1]}). +hibernate_in_trans_opts(false) -> + (#trans_opts{})#trans_opts.hibernate; +hibernate_in_trans_opts(#trans_opts{hibernate = Hibernate}) -> + Hibernate. + parse_actions(false, Debug, S, Actions) -> parse_actions(true, Debug, S, Actions, #trans_opts{}); parse_actions(TransOpts, Debug, S, Actions) -> @@ -1234,6 +1261,11 @@ parse_actions(StateCall, Debug, S, [Action|Actions], TransOpts) -> parse_actions( StateCall, Debug, S, Actions, TransOpts#trans_opts{postpone = true}); + postpone -> + [error, + {bad_state_enter_action_from_state_function,Action}, + ?STACKTRACE(), + Debug]; %% {next_event,Type,Content} -> parse_actions_next_event( @@ -1286,7 +1318,8 @@ parse_actions_next_event( next_events_r = [{Type,Content}|NextEventsR]}); _ -> [error, - {bad_action_from_state_function,{next_events,Type,Content}}, + {bad_state_enter_action_from_state_function, + {next_event,Type,Content}}, ?STACKTRACE(), ?not_sys_debug] end; @@ -1303,22 +1336,23 @@ parse_actions_next_event( next_events_r = [{Type,Content}|NextEventsR]}); _ -> [error, - {bad_action_from_state_function,{next_events,Type,Content}}, + {bad_state_enter_action_from_state_function, + {next_event,Type,Content}}, ?STACKTRACE(), Debug] end. parse_actions_timeout( StateCall, Debug, S, Actions, TransOpts, - {TimerType,Time,TimerMsg,TimerOpts} = AbsoluteTimeout) -> + {TimeoutType,Time,TimerMsg,TimerOpts} = AbsoluteTimeout) -> %% - case classify_timer(Time, listify(TimerOpts)) of + case classify_timeout(TimeoutType, Time, listify(TimerOpts)) of absolute -> parse_actions_timeout_add( StateCall, Debug, S, Actions, TransOpts, AbsoluteTimeout); relative -> - RelativeTimeout = {TimerType,Time,TimerMsg}, + RelativeTimeout = {TimeoutType,Time,TimerMsg}, parse_actions_timeout_add( StateCall, Debug, S, Actions, TransOpts, RelativeTimeout); @@ -1330,8 +1364,8 @@ parse_actions_timeout( end; parse_actions_timeout( StateCall, Debug, S, Actions, TransOpts, - {_,Time,_} = RelativeTimeout) -> - case classify_timer(Time, []) of + {TimeoutType,Time,_} = RelativeTimeout) -> + case classify_timeout(TimeoutType, Time, []) of relative -> parse_actions_timeout_add( StateCall, Debug, S, Actions, @@ -1344,14 +1378,16 @@ parse_actions_timeout( end; parse_actions_timeout( StateCall, Debug, S, Actions, TransOpts, - Timeout) -> - case classify_timer(Timeout, []) of + Time) -> + case classify_timeout(timeout, Time, []) of relative -> + RelativeTimeout = {timeout,Time,Time}, parse_actions_timeout_add( - StateCall, Debug, S, Actions, TransOpts, Timeout); + StateCall, Debug, S, Actions, + TransOpts, RelativeTimeout); badarg -> [error, - {bad_action_from_state_function,Timeout}, + {bad_action_from_state_function,Time}, ?STACKTRACE(), Debug] end. @@ -1637,10 +1673,15 @@ call_state_function( %% -> absolute | relative | badarg -classify_timer(Time, Opts) -> - classify_timer(Time, Opts, false). -%% -classify_timer(Time, [], Abs) -> +classify_timeout(TimeoutType, Time, Opts) -> + case timeout_event_type(TimeoutType) of + true -> + classify_time(false, Time, Opts); + false -> + badarg + end. + +classify_time(Abs, Time, []) -> case Abs of true when is_integer(Time); @@ -1653,9 +1694,9 @@ classify_timer(Time, [], Abs) -> _ -> badarg end; -classify_timer(Time, [{abs,Abs}|Opts], _) when is_boolean(Abs) -> - classify_timer(Time, Opts, Abs); -classify_timer(_, Opts, _) when is_list(Opts) -> +classify_time(_, Time, [{abs,Abs}|Opts]) when is_boolean(Abs) -> + classify_time(Abs, Time, Opts); +classify_time(_, _, Opts) when is_list(Opts) -> badarg. %% Stop and start timers as well as create timeout zero events @@ -1686,15 +1727,7 @@ parse_timers( {TimerType,Time,TimerMsg} -> parse_timers( TimerRefs, Timers, TimeoutsR, Seen, TimeoutEvents, - TimerType, Time, TimerMsg, []); - 0 -> - parse_timers( - TimerRefs, Timers, TimeoutsR, Seen, TimeoutEvents, - timeout, zero, 0, []); - Time -> - parse_timers( - TimerRefs, Timers, TimeoutsR, Seen, TimeoutEvents, - timeout, Time, Time, []) + TimerType, Time, TimerMsg, []) end. parse_timers( @@ -1821,9 +1854,7 @@ terminate( catch _ -> ok; C:R:ST -> - error_info( - C, R, ST, S, Q, - format_status(terminate, get(), S)), + error_info(C, R, ST, S, Q), sys:print_log(Debug), erlang:raise(C, R, ST) end; @@ -1839,9 +1870,7 @@ terminate( {shutdown,_} -> terminate_sys_debug(Debug, S, State, Reason); _ -> - error_info( - Class, Reason, Stacktrace, S, Q, - format_status(terminate, get(), S)), + error_info(Class, Reason, Stacktrace, S, Q), sys:print_log(Debug) end, case Stacktrace of @@ -1861,8 +1890,28 @@ error_info( name = Name, callback_mode = CallbackMode, state_enter = StateEnter, - postponed = P}, - Q, FmtData) -> + postponed = P} = S, + Q) -> + ?LOG_ERROR(#{label=>{gen_statem,terminate}, + name=>Name, + queue=>Q, + postponed=>P, + callback_mode=>CallbackMode, + state_enter=>StateEnter, + state=>format_status(terminate, get(), S), + reason=>{Class,Reason,Stacktrace}}, + #{domain=>[beam,erlang,otp], + report_cb=>fun gen_statem:format_log/1, + error_logger=>#{tag=>error}}). + +format_log(#{label:={gen_statem,terminate}, + name:=Name, + queue:=Q, + postponed:=P, + callback_mode:=CallbackMode, + state_enter:=StateEnter, + state:=FmtData, + reason:={Class,Reason,Stacktrace}}) -> {FixedReason,FixedStacktrace} = case Stacktrace of [{M,F,Args,_}|ST] @@ -1889,7 +1938,7 @@ error_info( _ -> {Reason,Stacktrace} end, [LimitedP, LimitedFmtData, LimitedFixedReason] = - [error_logger:limit_term(D) || D <- [P, FmtData, FixedReason]], + [logger:limit_term(D) || D <- [P, FmtData, FixedReason]], CBMode = case StateEnter of true -> @@ -1897,48 +1946,46 @@ error_info( false -> CallbackMode end, - error_logger:format( - "** State machine ~tp terminating~n" ++ - case Q of - [] -> ""; - _ -> "** Last event = ~tp~n" - end ++ - "** When server state = ~tp~n" ++ - "** Reason for termination = ~w:~tp~n" ++ - "** Callback mode = ~p~n" ++ - case Q of - [_,_|_] -> "** Queued = ~tp~n"; - _ -> "" - end ++ - case P of - [] -> ""; - _ -> "** Postponed = ~tp~n" - end ++ - case FixedStacktrace of - [] -> ""; - _ -> "** Stacktrace =~n** ~tp~n" - end, - [Name | - case Q of - [] -> []; - [Event|_] -> [Event] - end] ++ - [LimitedFmtData, - Class,LimitedFixedReason, - CBMode] ++ - case Q of - [_|[_|_] = Events] -> [Events]; - _ -> [] - end ++ - case P of - [] -> []; - _ -> [LimitedP] - end ++ - case FixedStacktrace of - [] -> []; - _ -> [FixedStacktrace] - end). - + {"** State machine ~tp terminating~n" ++ + case Q of + [] -> ""; + _ -> "** Last event = ~tp~n" + end ++ + "** When server state = ~tp~n" ++ + "** Reason for termination = ~w:~tp~n" ++ + "** Callback mode = ~p~n" ++ + case Q of + [_,_|_] -> "** Queued = ~tp~n"; + _ -> "" + end ++ + case P of + [] -> ""; + _ -> "** Postponed = ~tp~n" + end ++ + case FixedStacktrace of + [] -> ""; + _ -> "** Stacktrace =~n** ~tp~n" + end, + [Name | + case Q of + [] -> []; + [Event|_] -> [Event] + end] ++ + [LimitedFmtData, + Class,LimitedFixedReason, + CBMode] ++ + case Q of + [_|[_|_] = Events] -> [Events]; + _ -> [] + end ++ + case P of + [] -> []; + _ -> [LimitedP] + end ++ + case FixedStacktrace of + [] -> []; + _ -> [FixedStacktrace] + end}. %% Call Module:format_status/2 or return a default value format_status( diff --git a/lib/stdlib/src/io_lib.erl b/lib/stdlib/src/io_lib.erl index e37c13093b..3a5aba60b4 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(), @@ -172,6 +185,21 @@ format(Format, Args) -> Other 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) -> + case catch io_lib_format:fwrite(Format, Args, Options) of + {'EXIT',_} -> + erlang:error(badarg, [Format, Args, Options]); + Other -> + Other + end. + -spec scan_format(Format, Data) -> FormatList when Format :: io:format(), Data :: [term()], @@ -197,6 +225,15 @@ unscan_format(FormatList) -> build_text(FormatList) -> io_lib_format:build(FormatList). +-spec build_text(FormatList, Options) -> chars() when + FormatList :: [char() | format_spec()], + Options :: [Option], + Option :: {'chars_limit', CharsLimit}, + CharsLimit :: chars_limit(). + +build_text(FormatList, Options) -> + io_lib_format:build(FormatList, Options). + -spec print(Term) -> chars() when Term :: term(). @@ -240,7 +277,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 +296,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 +312,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 +351,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 +362,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 +388,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 @@ -947,7 +1013,7 @@ limit(T, D) when is_tuple(T) -> 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,6 +1025,11 @@ 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. Instead of subtracting one diff --git a/lib/stdlib/src/io_lib_format.erl b/lib/stdlib/src/io_lib_format.erl index 64edbf1824..c814ab50d4 100644 --- a/lib/stdlib/src/io_lib_format.erl +++ b/lib/stdlib/src/io_lib_format.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. @@ -21,7 +21,8 @@ %% Formatting functions of io library. --export([fwrite/2,fwrite_g/1,indentation/2,scan/2,unscan/1,build/1]). +-export([fwrite/2,fwrite/3,fwrite_g/1,indentation/2,scan/2,unscan/1, + build/1, build/2]). %% Format the arguments in Args after string Format. Just generate %% an error if there is an error in the arguments. @@ -45,14 +46,42 @@ fwrite(Format, Args) -> build(scan(Format, Args)). +-spec fwrite(Format, Data, Options) -> FormatList when + Format :: io:format(), + Data :: [term()], + FormatList :: [char() | io_lib:format_spec()], + Options :: [Option], + Option :: {'chars_limit', CharsLimit}, + CharsLimit :: io_lib:chars_limit(). + +fwrite(Format, Args, Options) -> + build(scan(Format, Args), Options). + %% Build the output text for a pre-parsed format list. -spec build(FormatList) -> io_lib:chars() when FormatList :: [char() | io_lib:format_spec()]. build(Cs) -> - Pc = pcount(Cs), - build(Cs, Pc, 0). + build(Cs, []). + +-spec build(FormatList, Options) -> io_lib:chars() when + FormatList :: [char() | io_lib:format_spec()], + Options :: [Option], + Option :: {'chars_limit', CharsLimit}, + CharsLimit :: io_lib:chars_limit(). + +build(Cs, Options) -> + CharsLimit = get_option(chars_limit, Options, -1), + Res1 = build_small(Cs), + {P, S, W, Other} = count_small(Res1), + case P + S + W of + 0 -> + Res1; + NumOfLimited -> + RemainingChars = sub(CharsLimit, Other), + build_limited(Res1, P, NumOfLimited, RemainingChars, 0) + end. %% Parse all control sequences in the format string. @@ -202,40 +231,77 @@ collect_cc([$~|Fmt], Args) when is_list(Args) -> {$~,[],Fmt,Args}; collect_cc([$n|Fmt], Args) when is_list(Args) -> {$n,[],Fmt,Args}; collect_cc([$i|Fmt], [A|Args]) -> {$i,[A],Fmt,Args}. -%% pcount([ControlC]) -> Count. -%% Count the number of print requests. - -pcount(Cs) -> pcount(Cs, 0). - -pcount([#{control_char := $p}|Cs], Acc) -> pcount(Cs, Acc+1); -pcount([#{control_char := $P}|Cs], Acc) -> pcount(Cs, Acc+1); -pcount([_|Cs], Acc) -> pcount(Cs, Acc); -pcount([], Acc) -> Acc. - -%% build([Control], Pc, Indentation) -> io_lib:chars(). +%% count_small([ControlC]) -> Count. +%% Count the number of big (pPwWsS) print requests and +%% number of characters of other print (small) requests. + +count_small(Cs) -> + count_small(Cs, #{p => 0, s => 0, w => 0, other => 0}). + +count_small([#{control_char := $p}|Cs], #{p := P} = Cnts) -> + count_small(Cs, Cnts#{p := P + 1}); +count_small([#{control_char := $P}|Cs], #{p := P} = Cnts) -> + count_small(Cs, Cnts#{p := P + 1}); +count_small([#{control_char := $w}|Cs], #{w := W} = Cnts) -> + count_small(Cs, Cnts#{w := W + 1}); +count_small([#{control_char := $W}|Cs], #{w := W} = Cnts) -> + count_small(Cs, Cnts#{w := W + 1}); +count_small([#{control_char := $s}|Cs], #{w := W} = Cnts) -> + count_small(Cs, Cnts#{w := W + 1}); +count_small([S|Cs], #{other := Other} = Cnts) when is_list(S) -> + count_small(Cs, Cnts#{other := Other + string:length(S)}); +count_small([C|Cs], #{other := Other} = Cnts) when is_integer(C) -> + count_small(Cs, Cnts#{other := Other + 1}); +count_small([], #{p := P, s := S, w := W, other := Other}) -> + {P, S, W, Other}. + +%% build_small([Control]) -> io_lib:chars(). +%% Interpret the control structures, but only the small ones. +%% The big ones are saved for later. +%% build_limited([Control], NumberOfPps, NumberOfLimited, +%% CharsLimit, Indentation) %% Interpret the control structures. Count the number of print %% remaining and only calculate indentation when necessary. Must also %% be smart when calculating indentation for characters in format. -build([#{control_char := C, args := As, width := F, adjust := Ad, - precision := P, pad_char := Pad, encoding := Enc, - strings := Str} | Cs], Pc0, I) -> - S = control(C, As, F, Ad, P, Pad, Enc, Str, I), - Pc1 = decr_pc(C, Pc0), +build_small([#{control_char := C, args := As, width := F, adjust := Ad, + precision := P, pad_char := Pad, encoding := Enc}=CC | Cs]) -> + case control_small(C, As, F, Ad, P, Pad, Enc) of + not_small -> [CC | build_small(Cs)]; + S -> lists:flatten(S) ++ build_small(Cs) + end; +build_small([C|Cs]) -> [C|build_small(Cs)]; +build_small([]) -> []. + +build_limited([#{control_char := C, args := As, width := F, adjust := Ad, + precision := P, pad_char := Pad, encoding := Enc, + strings := Str} | Cs], NumOfPs0, Count0, MaxLen0, I) -> + MaxChars = if + MaxLen0 < 0 -> MaxLen0; + true -> MaxLen0 div Count0 + end, + S = control_limited(C, As, F, Ad, P, Pad, Enc, Str, MaxChars, I), + Len = string:length(S), + NumOfPs = decr_pc(C, NumOfPs0), + Count = Count0 - 1, + MaxLen = sub(MaxLen0, Len), if - Pc1 > 0 -> [S|build(Cs, Pc1, indentation(S, I))]; - true -> [S|build(Cs, Pc1, I)] + NumOfPs > 0 -> [S|build_limited(Cs, NumOfPs, Count, + MaxLen, indentation(S, I))]; + true -> [S|build_limited(Cs, NumOfPs, Count, MaxLen, I)] end; -build([$\n|Cs], Pc, _I) -> [$\n|build(Cs, Pc, 0)]; -build([$\t|Cs], Pc, I) -> [$\t|build(Cs, Pc, ((I + 8) div 8) * 8)]; -build([C|Cs], Pc, I) -> [C|build(Cs, Pc, I+1)]; -build([], _Pc, _I) -> []. +build_limited([$\n|Cs], NumOfPs, Count, MaxLen, _I) -> + [$\n|build_limited(Cs, NumOfPs, Count, MaxLen, 0)]; +build_limited([$\t|Cs], NumOfPs, Count, MaxLen, I) -> + [$\t|build_limited(Cs, NumOfPs, Count, MaxLen, ((I + 8) div 8) * 8)]; +build_limited([C|Cs], NumOfPs, Count, MaxLen, I) -> + [C|build_limited(Cs, NumOfPs, Count, MaxLen, I+1)]; +build_limited([], _, _, _, _) -> []. decr_pc($p, Pc) -> Pc - 1; decr_pc($P, Pc) -> Pc - 1; decr_pc(_, Pc) -> Pc. - %% Calculate the indentation of the end of a string given its start %% indentation. We assume tabs at 8 cols. @@ -251,67 +317,74 @@ indentation([C|Cs], I) -> indentation(Cs, indentation(C, I)); indentation([], I) -> I. -%% control(FormatChar, [Argument], FieldWidth, Adjust, Precision, PadChar, -%% Encoding, Indentation) -> String -%% This is the main dispatch function for the various formatting commands. -%% Field widths and precisions have already been calculated. - -control($w, [A], F, Adj, P, Pad, Enc, _Str, _I) -> - term(io_lib:write(A, [{depth,-1}, {encoding, Enc}]), F, Adj, P, Pad); -control($p, [A], F, Adj, P, Pad, Enc, Str, I) -> - print(A, -1, F, Adj, P, Pad, Enc, Str, I); -control($W, [A,Depth], F, Adj, P, Pad, Enc, _Str, _I) when is_integer(Depth) -> - term(io_lib:write(A, [{depth,Depth}, {encoding, Enc}]), F, Adj, P, Pad); -control($P, [A,Depth], F, Adj, P, Pad, Enc, Str, I) when is_integer(Depth) -> - print(A, Depth, F, Adj, P, Pad, Enc, Str, I); -control($s, [A], F, Adj, P, Pad, latin1, _Str, _I) when is_atom(A) -> +%% control_small(FormatChar, [Argument], FieldWidth, Adjust, Precision, +%% PadChar, Encoding) -> String +%% control_limited(FormatChar, [Argument], FieldWidth, Adjust, Precision, +%% PadChar, Encoding, StringP, ChrsLim, Indentation) -> String +%% These are the dispatch functions for the various formatting controls. + +control_small($s, [A], F, Adj, P, Pad, latin1) when is_atom(A) -> L = iolist_to_chars(atom_to_list(A)), string(L, F, Adj, P, Pad); -control($s, [A], F, Adj, P, Pad, unicode, _Str, _I) when is_atom(A) -> +control_small($s, [A], F, Adj, P, Pad, unicode) when is_atom(A) -> string(atom_to_list(A), F, Adj, P, Pad); -control($s, [L0], F, Adj, P, Pad, latin1, _Str, _I) -> - L = iolist_to_chars(L0), - string(L, F, Adj, P, Pad); -control($s, [L0], F, Adj, P, Pad, unicode, _Str, _I) -> - L = cdata_to_chars(L0), - uniconv(string(L, F, Adj, P, Pad)); -control($e, [A], F, Adj, P, Pad, _Enc, _Str, _I) when is_float(A) -> +control_small($e, [A], F, Adj, P, Pad, _Enc) when is_float(A) -> fwrite_e(A, F, Adj, P, Pad); -control($f, [A], F, Adj, P, Pad, _Enc, _Str, _I) when is_float(A) -> +control_small($f, [A], F, Adj, P, Pad, _Enc) when is_float(A) -> fwrite_f(A, F, Adj, P, Pad); -control($g, [A], F, Adj, P, Pad, _Enc, _Str, _I) when is_float(A) -> +control_small($g, [A], F, Adj, P, Pad, _Enc) when is_float(A) -> fwrite_g(A, F, Adj, P, Pad); -control($b, [A], F, Adj, P, Pad, _Enc, _Str, _I) when is_integer(A) -> +control_small($b, [A], F, Adj, P, Pad, _Enc) when is_integer(A) -> unprefixed_integer(A, F, Adj, base(P), Pad, true); -control($B, [A], F, Adj, P, Pad, _Enc, _Str, _I) when is_integer(A) -> +control_small($B, [A], F, Adj, P, Pad, _Enc) when is_integer(A) -> unprefixed_integer(A, F, Adj, base(P), Pad, false); -control($x, [A,Prefix], F, Adj, P, Pad, _Enc, _Str, _I) when is_integer(A), - is_atom(Prefix) -> +control_small($x, [A,Prefix], F, Adj, P, Pad, _Enc) when is_integer(A), + is_atom(Prefix) -> prefixed_integer(A, F, Adj, base(P), Pad, atom_to_list(Prefix), true); -control($x, [A,Prefix], F, Adj, P, Pad, _Enc, _Str, _I) when is_integer(A) -> +control_small($x, [A,Prefix], F, Adj, P, Pad, _Enc) when is_integer(A) -> true = io_lib:deep_char_list(Prefix), %Check if Prefix a character list prefixed_integer(A, F, Adj, base(P), Pad, Prefix, true); -control($X, [A,Prefix], F, Adj, P, Pad, _Enc, _Str, _I) when is_integer(A), - is_atom(Prefix) -> +control_small($X, [A,Prefix], F, Adj, P, Pad, _Enc) when is_integer(A), + is_atom(Prefix) -> prefixed_integer(A, F, Adj, base(P), Pad, atom_to_list(Prefix), false); -control($X, [A,Prefix], F, Adj, P, Pad, _Enc, _Str, _I) when is_integer(A) -> +control_small($X, [A,Prefix], F, Adj, P, Pad, _Enc) when is_integer(A) -> true = io_lib:deep_char_list(Prefix), %Check if Prefix a character list prefixed_integer(A, F, Adj, base(P), Pad, Prefix, false); -control($+, [A], F, Adj, P, Pad, _Enc, _Str, _I) when is_integer(A) -> +control_small($+, [A], F, Adj, P, Pad, _Enc) when is_integer(A) -> Base = base(P), Prefix = [integer_to_list(Base), $#], prefixed_integer(A, F, Adj, Base, Pad, Prefix, true); -control($#, [A], F, Adj, P, Pad, _Enc, _Str, _I) when is_integer(A) -> +control_small($#, [A], F, Adj, P, Pad, _Enc) when is_integer(A) -> Base = base(P), Prefix = [integer_to_list(Base), $#], prefixed_integer(A, F, Adj, Base, Pad, Prefix, false); -control($c, [A], F, Adj, P, Pad, unicode, _Str, _I) when is_integer(A) -> +control_small($c, [A], F, Adj, P, Pad, unicode) when is_integer(A) -> char(A, F, Adj, P, Pad); -control($c, [A], F, Adj, P, Pad, _Enc, _Str, _I) when is_integer(A) -> +control_small($c, [A], F, Adj, P, Pad, _Enc) when is_integer(A) -> char(A band 255, F, Adj, P, Pad); -control($~, [], F, Adj, P, Pad, _Enc, _Str, _I) -> char($~, F, Adj, P, Pad); -control($n, [], F, Adj, P, Pad, _Enc, _Str, _I) -> newline(F, Adj, P, Pad); -control($i, [_A], _F, _Adj, _P, _Pad, _Enc, _Str, _I) -> []. +control_small($~, [], F, Adj, P, Pad, _Enc) -> char($~, F, Adj, P, Pad); +control_small($n, [], F, Adj, P, Pad, _Enc) -> newline(F, Adj, P, Pad); +control_small($i, [_A], _F, _Adj, _P, _Pad, _Enc) -> []; +control_small(_C, _As, _F, _Adj, _P, _Pad, _Enc) -> not_small. + +control_limited($s, [L0], F, Adj, P, Pad, latin1, _Str, CL, _I) -> + L = iolist_to_chars(L0), + string(limit_string(L, F, CL), limit_field(F, CL), Adj, P, Pad); +control_limited($s, [L0], F, Adj, P, Pad, unicode, _Str, CL, _I) -> + L = cdata_to_chars(L0), + uniconv(string(limit_string(L, F, CL), limit_field(F, CL), Adj, P, Pad)); +control_limited($w, [A], F, Adj, P, Pad, Enc, _Str, CL, _I) -> + Chars = io_lib:write(A, [{depth, -1}, {encoding, Enc}, {chars_limit, CL}]), + term(Chars, F, Adj, P, Pad); +control_limited($p, [A], F, Adj, P, Pad, Enc, Str, CL, I) -> + print(A, -1, F, Adj, P, Pad, Enc, Str, CL, I); +control_limited($W, [A,Depth], F, Adj, P, Pad, Enc, _Str, CL, _I) + when is_integer(Depth) -> + Chars = io_lib:write(A, [{depth, Depth}, {encoding, Enc}, {chars_limit, CL}]), + term(Chars, F, Adj, P, Pad); +control_limited($P, [A,Depth], F, Adj, P, Pad, Enc, Str, CL, I) + when is_integer(Depth) -> + print(A, Depth, F, Adj, P, Pad, Enc, Str, CL, I). -ifdef(UNICODE_AS_BINARIES). uniconv(C) -> @@ -348,12 +421,13 @@ term(T, F, Adj, P0, Pad) -> %% Print a term. Field width sets maximum line length, Precision sets %% initial indentation. -print(T, D, none, Adj, P, Pad, E, Str, I) -> - print(T, D, 80, Adj, P, Pad, E, Str, I); -print(T, D, F, Adj, none, Pad, E, Str, I) -> - print(T, D, F, Adj, I+1, Pad, E, Str, I); -print(T, D, F, right, P, _Pad, Enc, Str, _I) -> - Options = [{column, P}, +print(T, D, none, Adj, P, Pad, E, Str, ChLim, I) -> + print(T, D, 80, Adj, P, Pad, E, Str, ChLim, I); +print(T, D, F, Adj, none, Pad, E, Str, ChLim, I) -> + print(T, D, F, Adj, I+1, Pad, E, Str, ChLim, I); +print(T, D, F, right, P, _Pad, Enc, Str, ChLim, _I) -> + Options = [{chars_limit, ChLim}, + {column, P}, {line_length, F}, {depth, D}, {encoding, Enc}, @@ -670,6 +744,18 @@ cdata_to_chars(B) when is_binary(B) -> _ -> binary_to_list(B) end. +limit_string(S, F, CharsLimit) when CharsLimit < 0; CharsLimit >= F -> S; +limit_string(S, _F, CharsLimit) -> + case string:length(S) =< CharsLimit of + true -> S; + false -> [string:slice(S, 0, sub(CharsLimit, 3)), "..."] + end. + +limit_field(F, CharsLimit) when CharsLimit < 0; F =:= none -> + F; +limit_field(F, CharsLimit) -> + max(3, min(F, CharsLimit)). + %% string(String, Field, Adjust, Precision, PadChar) string(S, none, _Adj, none, _Pad) -> S; @@ -783,3 +869,15 @@ lowercase([H|T]) -> [H|lowercase(T)]; lowercase([]) -> []. + +%% Make sure T does change sign. +sub(T, _) when T < 0 -> T; +sub(T, E) when T >= E -> T - E; +sub(_, _) -> 0. + +get_option(Key, TupleList, Default) -> + case lists:keyfind(Key, 1, TupleList) of + false -> Default; + {Key, Value} -> Value; + _ -> Default + end. diff --git a/lib/stdlib/src/io_lib_pretty.erl b/lib/stdlib/src/io_lib_pretty.erl index 89e1931d2d..3d5a979b3e 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. @@ -26,6 +26,9 @@ -export([print/1,print/2,print/3,print/4,print/5,print/6]). +%% To be used by io_lib only. +-export([intermediate/6, write/1]). + %%% %%% Exported functions %%% @@ -45,20 +48,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 +74,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 +91,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 +141,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 +162,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 +199,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 +224,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 +232,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 +240,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 +250,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 +266,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 +274,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 +301,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 +322,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 +332,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 +363,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 +407,359 @@ 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(), pos_integer(), 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, string: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 + string: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 + string: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 + string:length(S), 3, More}; + false -> + case io_lib:write_binary(Bin, D, T) of + {S, <<>>} -> + {{bin, S}, iolist_size(S), 0, no_more}; + {S, _Rest} -> + More = fun(T1, Dd) -> + ?FUNCTION_NAME(Bin, D+Dd, T1, RF, Enc, Str) + end, + {{bin, S}, iolist_size(S), 3, More} + end 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, D - 1, 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, _D0, _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, D0, T, RF, Enc, Str) when D =:= 1; T =:= 0-> + More = fun(T1, Dd) -> + ?FUNCTION_NAME(Term, D+Dd, D0, T1, RF, Enc, Str) + end, + {dots, 3, 3, More}; +print_length_map_pairs({K, V, Iter}, D, D0, T, RF, Enc, Str) -> + Pair1 = print_length_map_pair(K, V, D0, tsub(T, 1), RF, Enc, Str), + {_, Len1, _, _} = Pair1, + Next = maps:next(Iter), + [Pair1 | + print_length_map_pairs(Next, D - 1, D0, 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_tuple1(Tuple, 1, 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_tuple1(Tuple, I, _D, _T, _RF, _Enc, _Str) + when I > tuple_size(Tuple) -> + []; +print_length_tuple1(Tuple, I, D, T, RF, Enc, Str) when D =:= 1; T =:= 0-> + More = fun(T1, Dd) -> ?FUNCTION_NAME(Tuple, I, D+Dd, T1, RF, Enc, Str) end, + {dots, 3, 3, More}; +print_length_tuple1(Tuple, I, D, T, RF, Enc, Str) -> + E = element(I, Tuple), + T1 = tsub(T, 1), + {_, Len1, _, _} = Elem1 = print_length(E, D - 1, T1, RF, Enc, Str), + T2 = tsub(T1, Len1), + [Elem1 | print_length_tuple1(Tuple, I + 1, D - 1, T2, RF, 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), - 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)}. - -print_length_fields([], _D, [], _RF, _Enc, _Str) -> + NameL = string:length(Name), + T1 = tsub(T, NameL+2), + L = print_length_fields(RDefs, D - 1, T1, Tuple, 2, RF, Enc, Str), + {Len, Dots} = list_length(L, NameL + 2, 0), + {{record, [{Name,NameL} | L]}, Len, Dots, no_more}. + +print_length_fields([], _D, _T, Tuple, I, _RF, _Enc, _Str) + when I > tuple_size(Tuple) -> []; -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, Tuple, I, RF, Enc, Str) + when D =:= 1; T =:= 0 -> + More = fun(T1, Dd) -> + ?FUNCTION_NAME(Term, D+Dd, T1, Tuple, I, RF, Enc, Str) + end, + {dots, 3, 3, More}; +print_length_fields([Def | Defs], D, T, Tuple, I, RF, Enc, Str) -> + E = element(I, Tuple), + T1 = tsub(T, 1), + Field1 = print_length_field(Def, D - 1, T1, E, RF, Enc, Str), + {_, Len1, _, _} = Field1, + T2 = tsub(T1, Len1), + [Field1 | + print_length_fields(Defs, D - 1, T2, Tuple, I + 1, 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 slice(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). +slice(L, N) -> + case string:length(L) =< N of + true -> + all; + false -> + {prefix, string:slice(L, 0, N)} + end. + +printable_bin0(Bin, D, T, Enc) -> + Len = case D >= 0 of + true -> + %% Use byte_size() also if Enc =/= latin1. + 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 -> % cannot happen + T + end, + printable_bin(Bin, Len, D, Enc). printable_bin(Bin, Len, D, latin1) -> N = erlang:min(20, Len), @@ -689,28 +871,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 +956,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 +972,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 +980,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 +1002,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 +1016,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 +1024,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 +1047,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 +1055,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 +1066,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 +1076,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/lists.erl b/lib/stdlib/src/lists.erl index af9d63ddd6..06c90c0280 100644 --- a/lib/stdlib/src/lists.erl +++ b/lib/stdlib/src/lists.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2016. 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. @@ -38,8 +38,8 @@ -export([all/2,any/2,map/2,flatmap/2,foldl/3,foldr/3,filter/2, partition/2,zf/2,filtermap/2, - mapfoldl/3,mapfoldr/3,foreach/2,takewhile/2,dropwhile/2,splitwith/2, - split/2, + mapfoldl/3,mapfoldr/3,foreach/2,takewhile/2,dropwhile/2, + search/2, splitwith/2,split/2, join/2]). %%% BIFs @@ -1399,6 +1399,19 @@ dropwhile(Pred, [Hd|Tail]=Rest) -> end; dropwhile(Pred, []) when is_function(Pred, 1) -> []. +-spec search(Pred, List) -> {value, Value} | false when + Pred :: fun((T) -> boolean()), + List :: [T], + Value :: T. + +search(Pred, [Hd|Tail]) -> + case Pred(Hd) of + true -> {value, Hd}; + false -> search(Pred, Tail) + end; +search(Pred, []) when is_function(Pred, 1) -> + false. + -spec splitwith(Pred, List) -> {List1, List2} when Pred :: fun((T) -> boolean()), List :: [T], diff --git a/lib/stdlib/src/ms_transform.erl b/lib/stdlib/src/ms_transform.erl index 6616e957c0..ec8cfd56c2 100644 --- a/lib/stdlib/src/ms_transform.erl +++ b/lib/stdlib/src/ms_transform.erl @@ -944,6 +944,7 @@ real_guard_function(node,1) -> true; real_guard_function(round,1) -> true; real_guard_function(size,1) -> true; real_guard_function(map_size,1) -> true; +real_guard_function(map_get,2) -> true; real_guard_function(tl,1) -> true; real_guard_function(trunc,1) -> true; real_guard_function(self,0) -> true; @@ -1115,5 +1116,3 @@ normalise_list([H|T]) -> [normalise(H)|normalise_list(T)]; normalise_list([]) -> []. - - diff --git a/lib/stdlib/src/ordsets.erl b/lib/stdlib/src/ordsets.erl index 569407f5ef..939e147ad8 100644 --- a/lib/stdlib/src/ordsets.erl +++ b/lib/stdlib/src/ordsets.erl @@ -19,7 +19,7 @@ -module(ordsets). --export([new/0,is_set/1,size/1,to_list/1,from_list/1]). +-export([new/0,is_set/1,size/1,is_empty/1,to_list/1,from_list/1]). -export([is_element/2,add_element/2,del_element/2]). -export([union/2,union/1,intersection/2,intersection/1]). -export([is_disjoint/2]). @@ -60,6 +60,13 @@ is_set([], _) -> true. size(S) -> length(S). +%% is_empty(OrdSet) -> boolean(). +%% Return 'true' if OrdSet is an empty set, otherwise 'false'. +-spec is_empty(Ordset) -> boolean() when + Ordset :: ordset(_). + +is_empty(S) -> S=:=[]. + %% to_list(OrdSet) -> [Elem]. %% Return the elements in OrdSet as a list. diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl index 122b476ddb..a17addcc42 100644 --- a/lib/stdlib/src/otp_internal.erl +++ b/lib/stdlib/src/otp_internal.erl @@ -604,57 +604,14 @@ obsolete_1(filename, find_src, 1) -> obsolete_1(filename, find_src, 2) -> {deprecated, "deprecated; use filelib:find_source/3 instead"}; +obsolete_1(erlang, get_stacktrace, 0) -> + {deprecated, "deprecated; use the new try/catch syntax for retrieving the stack backtrace"}; + %% Removed in OTP 20. obsolete_1(erlang, hash, 2) -> {removed, {erlang, phash2, 2}, "20.0"}; -%% Added in OTP-21 -obsolete_1(string, len, 1) -> - {deprecated, "deprecated; use string:length/3 instead"}; -obsolete_1(string, concat, 2) -> - {deprecated, "deprecated; use [Str1,Str2] instead"}; -obsolete_1(string, str, 2) -> - {deprecated, "deprecated; use string:find/2 instead"}; -obsolete_1(string, rstr, 2) -> - {deprecated, "deprecated; use string:find/3 instead"}; -obsolete_1(string, chr, 2) -> - {deprecated, "deprecated; use string:find/2 instead"}; -obsolete_1(string, rchr, 2) -> - {deprecated, "deprecated; use string:find/3 instead"}; -obsolete_1(string, span, 2) -> - {deprecated, "deprecated; use string:take/2 instead"}; -obsolete_1(string, cspan, 2) -> - {deprecated, "deprecated; use string:take/3 instead"}; -obsolete_1(string, substr, _) -> - {deprecated, "deprecated; use string:slice/3 instead"}; -obsolete_1(string, tokens, 2) -> - {deprecated, "deprecated; use string:lexemes/2 instead"}; -obsolete_1(string, chars, _) -> - {deprecated, "deprecated; use lists:duplicate/2 instead"}; -obsolete_1(string, copies, _) -> - {deprecated, "deprecated; use lists:duplicate/2 instead"}; -obsolete_1(string, words, _) -> - {deprecated, "deprecated; use string:lexemes/2 instead"}; -obsolete_1(string, strip, _) -> - {deprecated, "deprecated; use string:trim/3 instead"}; -obsolete_1(string, sub_word, _) -> - {deprecated, "deprecated; use string:nth_lexeme/3 instead"}; -obsolete_1(string, sub_string, _) -> - {deprecated, "deprecated; use string:slice/3 instead"}; -obsolete_1(string, left, _) -> - {deprecated, "deprecated; use string:pad/3 instead"}; -obsolete_1(string, right, _) -> - {deprecated, "deprecated; use string:pad/3 instead"}; -obsolete_1(string, centre, _) -> - {deprecated, "deprecated; use string:pad/3 instead"}; -obsolete_1(string, join, _) -> - {deprecated, "deprecated; use lists:join/2 instead"}; -obsolete_1(string, to_upper, _) -> - {deprecated, "deprecated; use string:uppercase/1 or string:titlecase/1 instead"}; -obsolete_1(string, to_lower, _) -> - {deprecated, "deprecated; use string:lowercase/1 or string:casefold/1 instead"}; - %% not obsolete obsolete_1(_, _, _) -> diff --git a/lib/stdlib/src/proc_lib.erl b/lib/stdlib/src/proc_lib.erl index 1991585c13..8d01840313 100644 --- a/lib/stdlib/src/proc_lib.erl +++ b/lib/stdlib/src/proc_lib.erl @@ -30,7 +30,7 @@ start/3, start/4, start/5, start_link/3, start_link/4, start_link/5, hibernate/3, init_ack/1, init_ack/2, - init_p/3,init_p/5,format/1,format/2,format/3, + init_p/3,init_p/5,format/1,format/2,format/3,report_cb/1, initial_call/1, translate_initial_call/1, stop/1, stop/3]). @@ -40,6 +40,8 @@ -export_type([spawn_option/0]). +-include("logger.hrl"). + %%----------------------------------------------------------------------------- -type priority_level() :: 'high' | 'low' | 'max' | 'normal'. @@ -503,10 +505,13 @@ crash_report(exit, normal, _, _) -> ok; crash_report(exit, shutdown, _, _) -> ok; crash_report(exit, {shutdown,_}, _, _) -> ok; crash_report(Class, Reason, StartF, Stacktrace) -> - OwnReport = my_info(Class, Reason, StartF, Stacktrace), - LinkReport = linked_info(self()), - Rep = [OwnReport,LinkReport], - error_logger:error_report(crash_report, Rep). + ?LOG_ERROR(#{label=>{proc_lib,crash}, + report=>[my_info(Class, Reason, StartF, Stacktrace), + linked_info(self())]}, + #{domain=>[beam,erlang,otp,sasl], + report_cb=>fun proc_lib:report_cb/1, + logger_formatter=>#{title=>"CRASH REPORT"}, + error_logger=>#{tag=>error_report,type=>crash_report}}). my_info(Class, Reason, [], Stacktrace) -> my_info_1(Class, Reason, Stacktrace); @@ -548,10 +553,10 @@ get_ancestors(Pid) -> %% assumed that all report handlers call proc_lib:format(). get_messages(Pid) -> Messages = get_process_messages(Pid), - {messages, error_logger:limit_term(Messages)}. + {messages, logger:limit_term(Messages)}. get_process_messages(Pid) -> - Depth = error_logger:get_format_depth(), + Depth = logger:get_format_depth(), case Pid =/= self() orelse Depth =:= unlimited of true -> {messages, Messages} = get_process_info(Pid, messages), @@ -581,7 +586,7 @@ get_cleaned_dictionary(Pid) -> cleaned_dict(Dict) -> CleanDict = clean_dict(Dict), - error_logger:limit_term(CleanDict). + logger:limit_term(CleanDict). clean_dict([{'$ancestors',_}|Dict]) -> clean_dict(Dict); @@ -742,9 +747,18 @@ check({badrpc,Error}) -> Error; check(Res) -> Res. %%% ----------------------------------------------------------- -%%% Format (and write) a generated crash info structure. +%%% Format a generated crash info structure. %%% ----------------------------------------------------------- +-spec report_cb(CrashReport) -> {Format,Args} when + CrashReport :: #{label=>{proc_lib,crash},report=>[term()]}, + Format :: io:format(), + Args :: [term()]. +report_cb(#{label:={proc_lib,crash}, + report:=CrashReport}) -> + Depth = logger:get_format_depth(), + get_format_and_args(CrashReport, utf8, Depth). + -spec format(CrashReport) -> string() when CrashReport :: [term()]. format(CrashReport) -> @@ -762,61 +776,74 @@ format(CrashReport, Encoding) -> Encoding :: latin1 | unicode | utf8, Depth :: unlimited | pos_integer(). -format([OwnReport,LinkReport], Encoding, Depth) -> +format(CrashReport, Encoding, Depth) -> + {F,A} = get_format_and_args(CrashReport, Encoding, Depth), + lists:flatten(io_lib:format(F,A)). + +get_format_and_args([OwnReport,LinkReport], Encoding, Depth) -> Extra = {Encoding,Depth}, MyIndent = " ", - OwnFormat = format_report(OwnReport, MyIndent, Extra), - LinkFormat = format_link_report(LinkReport, MyIndent, Extra), - Str = io_lib:format(" crasher:~n~ts neighbours:~n~ts", - [OwnFormat, LinkFormat]), - lists:flatten(Str). + {OwnFormat,OwnArgs} = format_report(OwnReport, MyIndent, Extra, [], []), + {LinkFormat,LinkArgs} = format_link_report(LinkReport, MyIndent, Extra, [], []), + {" crasher:~n"++OwnFormat++" neighbours:~n"++LinkFormat,OwnArgs++LinkArgs}. -format_link_report([Link|Reps], Indent, Extra) -> +format_link_report([], _Indent, _Extra, Format, Args) -> + {lists:flatten(lists:reverse(Format)),lists:append(lists:reverse(Args))}; +format_link_report([Link|Reps], Indent, Extra, Format, Args) -> Rep = case Link of {neighbour,Rep0} -> Rep0; _ -> Link end, LinkIndent = [" ",Indent], - [Indent,"neighbour:\n",format_report(Rep, LinkIndent, Extra)| - format_link_report(Reps, Indent, Extra)]; -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]). - -format_rep([{initial_call,InitialCall}|Rep], Indent, Extra) -> - [format_mfa(Indent, InitialCall, Extra)|format_rep(Rep, Indent, Extra)]; -format_rep([{error_info,{Class,Reason,StackTrace}}|Rep], Indent, Extra) -> - [format_exception(Class, Reason, StackTrace, Extra)| - format_rep(Rep, Indent, Extra)]; -format_rep([{Tag,Data}|Rep], Indent, Extra) -> - [format_tag(Indent, Tag, Data, Extra)|format_rep(Rep, Indent, Extra)]; -format_rep(_, _, _Extra) -> - []. - -format_exception(Class, Reason, StackTrace, {Enc,_}=Extra) -> - PF = pp_fun(Extra), - StackFun = fun(M, _F, _A) -> (M =:= erl_eval) or (M =:= ?MODULE) end, - %% EI = " exception: ", - EI = " ", - [EI, lib:format_exception(1+length(EI), Class, Reason, - StackTrace, StackFun, PF, Enc), "\n"]. + {LinkFormat,LinkArgs} = format_report(Rep, LinkIndent, Extra, [], []), + F = "~sneighbour:\n"++LinkFormat, + A = [Indent|LinkArgs], + format_link_report(Reps, Indent, Extra, [F|Format], [A|Args]); +format_link_report(Rep, Indent, Extra, Format, Args) -> + {F,A} = format_report(Rep, Indent, Extra, [], []), + format_link_report([], Indent, Extra, [F|Format],[A|Args]). + +format_report([], _Indent, _Extra, Format, Args) -> + {lists:flatten(lists:reverse(Format)),lists:append(lists:reverse(Args))}; +format_report([Rep|Reps], Indent, Extra, Format, Args) -> + {F,A} = format_rep(Rep, Indent, Extra), + format_report(Reps, Indent, Extra, [F|Format], [A|Args]); +format_report(Rep, Indent, {Enc,unlimited}=Extra, Format, Args) -> + {F,A} = {"~s~"++modifier(Enc)++"p~n", [Indent, Rep]}, + format_report([], Indent, Extra, [F|Format], [A|Args]); +format_report(Rep, Indent, {Enc,Depth}=Extra, Format, Args) -> + {F,A} = {"~s~"++modifier(Enc)++"P~n", [Indent, Rep, Depth]}, + format_report([], Indent, Extra, [F|Format], [A|Args]). + +format_rep({initial_call,InitialCall}, Indent, Extra) -> + format_mfa(Indent, InitialCall, Extra); +format_rep({error_info,{Class,Reason,StackTrace}}, _Indent, Extra) -> + {lists:flatten(format_exception(Class, Reason, StackTrace, Extra)),[]}; +format_rep({Tag,Data}, Indent, Extra) -> + format_tag(Indent, Tag, Data, Extra). format_mfa(Indent, {M,F,Args}=StartF, {Enc,_}=Extra) -> try A = length(Args), - [Indent,"initial call: ",atom_to_list(M),$:,to_string(F, Enc),$/, - integer_to_list(A),"\n"] + {lists:flatten([Indent,"initial call: ",atom_to_list(M), + $:,to_string(F, Enc),$/,integer_to_list(A),"\n"]),[]} catch error:_ -> format_tag(Indent, initial_call, StartF, Extra) end. +format_tag(Indent, Tag, Data, {Enc,Depth}) -> + {P,Tl} = p(Enc, Depth), + {"~s~p: ~80.18" ++ P ++ "\n", [Indent, Tag, Data|Tl]}. + +format_exception(Class, Reason, StackTrace, {Enc,_}=Extra) -> + PF = pp_fun(Extra), + StackFun = fun(M, _F, _A) -> (M =:= erl_eval) or (M =:= ?MODULE) end, + %% EI = " exception: ", + EI = " ", + [EI, lib:format_exception(1+length(EI), Class, Reason, + StackTrace, StackFun, PF, Enc), "\n"]. + to_string(A, latin1) -> io_lib:write_atom_as_latin1(A); to_string(A, _) -> @@ -828,10 +855,6 @@ pp_fun({Enc,Depth}) -> io_lib:format("~." ++ integer_to_list(I) ++ P, [Term|Tl]) 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", []}; diff --git a/lib/stdlib/src/sets.erl b/lib/stdlib/src/sets.erl index c65a13b22e..ac0fc80526 100644 --- a/lib/stdlib/src/sets.erl +++ b/lib/stdlib/src/sets.erl @@ -37,7 +37,7 @@ -module(sets). %% Standard interface. --export([new/0,is_set/1,size/1,to_list/1,from_list/1]). +-export([new/0,is_set/1,size/1,is_empty/1,to_list/1,from_list/1]). -export([is_element/2,add_element/2,del_element/2]). -export([union/2,union/1,intersection/2,intersection/1]). -export([is_disjoint/2]). @@ -96,6 +96,12 @@ is_set(_) -> false. Set :: set(). size(S) -> S#set.size. +%% is_empty(Set) -> boolean(). +%% Return 'true' if Set is an empty set, otherwise 'false'. +-spec is_empty(Set) -> boolean() when + Set :: set(). +is_empty(S) -> S#set.size=:=0. + %% to_list(Set) -> [Elem]. %% Return the elements in Set as a list. -spec to_list(Set) -> List when 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())). diff --git a/lib/stdlib/src/stdlib.appup.src b/lib/stdlib/src/stdlib.appup.src index e4e3fb83e9..8d1cc09a8b 100644 --- a/lib/stdlib/src/stdlib.appup.src +++ b/lib/stdlib/src/stdlib.appup.src @@ -18,7 +18,9 @@ %% %CopyrightEnd% {"%VSN%", %% Up from - max one major revision back - [{<<"3\\.4(\\.[0-9]+)*">>,[restart_new_emulator]}], % OTP-20.* + [{<<"3\\.4(\\.[0-9]+)*">>,[restart_new_emulator]}, % OTP-20.* + {<<"3\\.5(\\.[0-9]+)*">>,[restart_new_emulator]}],% OTP-21.* %% Down to - max one major revision back - [{<<"3\\.4(\\.[0-9]+)*">>,[restart_new_emulator]}] % OTP-20.* + [{<<"3\\.4(\\.[0-9]+)*">>,[restart_new_emulator]}, % OTP-20.* + {<<"3\\.5(\\.[0-9]+)*">>,[restart_new_emulator]}] % OTP-20.* }. diff --git a/lib/stdlib/src/string.erl b/lib/stdlib/src/string.erl index 4e89819e41..0736374f21 100644 --- a/lib/stdlib/src/string.erl +++ b/lib/stdlib/src/string.erl @@ -88,16 +88,6 @@ %%% May be removed -export([list_to_float/1, list_to_integer/1]). --deprecated([{len,1},{concat,2}, - {str,2},{chr,2},{rchr,2},{rstr,2}, - {span,2},{cspan,2},{substr,'_'},{tokens,2}, - {chars,'_'}, - {copies,2},{words,'_'},{strip,'_'}, - {sub_word,'_'},{left,'_'},{right,'_'}, - {sub_string,'_'},{centre,'_'},{join,2}, - {to_upper,1}, {to_lower,1} - ]). - %% Uses bifs: string:list_to_float/1 and string:list_to_integer/1 -spec list_to_float(String) -> {Float, Rest} | {'error', Reason} when String :: string(), diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl index e56415650f..eb46ac611a 100644 --- a/lib/stdlib/src/supervisor.erl +++ b/lib/stdlib/src/supervisor.erl @@ -35,6 +35,20 @@ %% For release_handler only -export([get_callback_module/1]). +-include("logger.hrl"). + +-define(report_error(Error, Reason, Child, SupName), + ?LOG_ERROR(#{label=>{supervisor,Error}, + report=>[{supervisor,SupName}, + {errorContext,Error}, + {reason,Reason}, + {offender,extract_child(Child)}]}, + #{domain=>[beam,erlang,otp,sasl], + report_cb=>fun logger:format_otp_report/1, + logger_formatter=>#{title=>"SUPERVISOR REPORT"}, + error_logger=>#{tag=>error_report, + type=>supervisor_report}})). + %%-------------------------------------------------------------------------- -export_type([sup_flags/0, child_spec/0, startchild_ret/0, strategy/0]). @@ -340,7 +354,7 @@ start_children(Children, SupName) -> {ok, Pid, _Extra} -> {update,Child#child{pid = Pid}}; {error, Reason} -> - report_error(start_error, Reason, Child, SupName), + ?report_error(start_error, Reason, Child, SupName), {abort,{failed_to_start_child,Id,Reason}} end end, @@ -565,8 +579,9 @@ handle_info({'EXIT', Pid, Reason}, State) -> end; handle_info(Msg, State) -> - error_logger:error_msg("Supervisor received unexpected message: ~tp~n", - [Msg]), + ?LOG_ERROR("Supervisor received unexpected message: ~tp~n",[Msg], + #{domain=>[beam,erlang,otp], + error_logger=>#{tag=>error}}), {noreply, State}. %% @@ -683,7 +698,7 @@ restart_child(Pid, Reason, State) -> end. do_restart(Reason, Child, State) when ?is_permanent(Child) -> - report_error(child_terminated, Reason, Child, State#state.name), + ?report_error(child_terminated, Reason, Child, State#state.name), restart(Child, State); do_restart(normal, Child, State) -> NState = del_child(Child, State), @@ -695,10 +710,10 @@ do_restart({shutdown, _Term}, Child, State) -> NState = del_child(Child, State), {ok, NState}; do_restart(Reason, Child, State) when ?is_transient(Child) -> - report_error(child_terminated, Reason, Child, State#state.name), + ?report_error(child_terminated, Reason, Child, State#state.name), restart(Child, State); do_restart(Reason, Child, State) when ?is_temporary(Child) -> - report_error(child_terminated, Reason, Child, State#state.name), + ?report_error(child_terminated, Reason, Child, State#state.name), NState = del_child(Child, State), {ok, NState}. @@ -718,7 +733,7 @@ restart(Child, State) -> Other end; {terminate, NState} -> - report_error(shutdown, reached_max_restart_intensity, + ?report_error(shutdown, reached_max_restart_intensity, Child, State#state.name), {shutdown, del_child(Child, NState)} end. @@ -745,7 +760,7 @@ restart(simple_one_for_one, Child, State0) -> NRestarts = State2#state.dynamic_restarts + 1, State3 = State2#state{dynamic_restarts = NRestarts}, NState = dyn_store(ROldPid, A, State3), - report_error(start_error, Error, Child, NState#state.name), + ?report_error(start_error, Error, Child, NState#state.name), {{try_again, ROldPid}, NState} end; restart(one_for_one, #child{id=Id} = Child, State) -> @@ -759,7 +774,7 @@ restart(one_for_one, #child{id=Id} = Child, State) -> {ok, NState}; {error, Reason} -> NState = set_pid(restarting(OldPid), Id, State), - report_error(start_error, Reason, Child, State#state.name), + ?report_error(start_error, Reason, Child, State#state.name), {{try_again,Id}, NState} end; restart(rest_for_one, #child{id=Id} = Child, #state{name=SupName} = State) -> @@ -820,7 +835,7 @@ do_terminate(Child, SupName) when is_pid(Child#child.pid) -> {error, normal} when not (?is_permanent(Child)) -> ok; {error, OtherReason} -> - report_error(shutdown_error, OtherReason, Child, SupName) + ?report_error(shutdown_error, OtherReason, Child, SupName) end, ok; do_terminate(_Child, _SupName) -> @@ -924,7 +939,7 @@ terminate_dynamic_children(State) -> end, %% Unroll stacked errors and report them dict:fold(fun(Reason, Ls, _) -> - report_error(shutdown_error, Reason, + ?report_error(shutdown_error, Reason, Child#child{pid=Ls}, State#state.name) end, ok, EStack). @@ -1385,14 +1400,6 @@ inPeriod(Then, Now, Period) -> %%% ------------------------------------------------------ %%% Error and progress reporting. %%% ------------------------------------------------------ - -report_error(Error, Reason, Child, SupName) -> - ErrorMsg = [{supervisor, SupName}, - {errorContext, Error}, - {reason, Reason}, - {offender, extract_child(Child)}], - error_logger:error_report(supervisor_report, ErrorMsg). - extract_child(Child) when is_list(Child#child.pid) -> [{nb_children, length(Child#child.pid)}, {id, Child#child.id}, @@ -1409,9 +1416,13 @@ extract_child(Child) -> {child_type, Child#child.child_type}]. report_progress(Child, SupName) -> - Progress = [{supervisor, SupName}, - {started, extract_child(Child)}], - error_logger:info_report(progress, Progress). + ?LOG_INFO(#{label=>{supervisor,progress}, + report=>[{supervisor,SupName}, + {started,extract_child(Child)}]}, + #{domain=>[beam,erlang,otp,sasl], + report_cb=>fun logger:format_otp_report/1, + logger_formatter=>#{title=>"PROGRESS REPORT"}, + error_logger=>#{tag=>info_report,type=>progress}}). format_status(terminate, [_PDict, State]) -> State; diff --git a/lib/stdlib/src/supervisor_bridge.erl b/lib/stdlib/src/supervisor_bridge.erl index af1e046d30..39372935fa 100644 --- a/lib/stdlib/src/supervisor_bridge.erl +++ b/lib/stdlib/src/supervisor_bridge.erl @@ -21,6 +21,8 @@ -behaviour(gen_server). +-include("logger.hrl"). + %% External exports -export([start_link/2, start_link/3]). %% Internal exports @@ -129,13 +131,22 @@ terminate_pid(Reason, #state{mod = Mod, child_state = ChildState}) -> Mod:terminate(Reason, ChildState). report_progress(Pid, Mod, StartArgs, SupName) -> - Progress = [{supervisor, SupName}, - {started, [{pid, Pid}, {mfa, {Mod, init, [StartArgs]}}]}], - error_logger:info_report(progress, Progress). + ?LOG_INFO(#{label=>{supervisor,progress}, + report=>[{supervisor, SupName}, + {started, [{pid, Pid}, + {mfa, {Mod, init, [StartArgs]}}]}]}, + #{domain=>[beam,erlang,otp,sasl], + report_cb=>fun logger:format_otp_report/1, + logger_formatter=>#{title=>"PROGRESS REPORT"}, + error_logger=>#{tag=>info_report,type=>progress}}). report_error(Error, Reason, #state{name = Name, pid = Pid, mod = Mod}) -> - ErrorMsg = [{supervisor, Name}, - {errorContext, Error}, - {reason, Reason}, - {offender, [{pid, Pid}, {mod, Mod}]}], - error_logger:error_report(supervisor_report, ErrorMsg). + ?LOG_ERROR(#{label=>{supervisor,error}, + report=>[{supervisor, Name}, + {errorContext, Error}, + {reason, Reason}, + {offender, [{pid, Pid}, {mod, Mod}]}]}, + #{domain=>[beam,erlang,otp,sasl], + report_cb=>fun logger:format_otp_report/1, + logger_formatter=>#{title=>"SUPERVISOR REPORT"}, + error_logger=>#{tag=>error_report,type=>supervisor_report}}). diff --git a/lib/stdlib/src/sys.erl b/lib/stdlib/src/sys.erl index 0c578acf21..0064414d6f 100644 --- a/lib/stdlib/src/sys.erl +++ b/lib/stdlib/src/sys.erl @@ -44,6 +44,7 @@ -type system_event() :: {'in', Msg :: _} | {'in', Msg :: _, From :: _} | {'out', Msg :: _, To :: _} + | {'out', Msg :: _, To :: _, State :: _} | term(). -opaque dbg_opt() :: {'trace', 'true'} | {'log', @@ -56,7 +57,8 @@ MessagesIn :: non_neg_integer(), MessagesOut :: non_neg_integer()}} | {'log_to_file', file:io_device()} - | {Func :: dbg_fun(), FuncState :: term()}. + | {Func :: dbg_fun(), FuncState :: term()} + | {FuncId :: term(), Func :: dbg_fun(), FuncState :: term()}. -type dbg_fun() :: fun((FuncState :: _, Event :: system_event(), ProcState :: _) -> 'done' | (NewFuncState :: _)). @@ -267,33 +269,41 @@ no_debug(Name, Timeout) -> send_system_msg(Name, {debug, no_debug}, Timeout). -spec install(Name, FuncSpec) -> 'ok' when Name :: name(), - FuncSpec :: {Func, FuncState}, + FuncSpec :: {Func, FuncState} | {FuncId, Func, FuncState}, + FuncId :: term(), Func :: dbg_fun(), FuncState :: term(). install(Name, {Func, FuncState}) -> - send_system_msg(Name, {debug, {install, {Func, FuncState}}}). + send_system_msg(Name, {debug, {install, {Func, FuncState}}}); +install(Name, {FuncId, Func, FuncState}) -> + send_system_msg(Name, {debug, {install, {FuncId, Func, FuncState}}}). -spec install(Name, FuncSpec, Timeout) -> 'ok' when Name :: name(), - FuncSpec :: {Func, FuncState}, + FuncSpec :: {Func, FuncState} | {FuncId, Func, FuncState}, + FuncId :: term(), Func :: dbg_fun(), FuncState :: term(), Timeout :: timeout(). install(Name, {Func, FuncState}, Timeout) -> - send_system_msg(Name, {debug, {install, {Func, FuncState}}}, Timeout). + send_system_msg(Name, {debug, {install, {Func, FuncState}}}, Timeout); +install(Name, {FuncId, Func, FuncState}, Timeout) -> + send_system_msg(Name, {debug, {install, {FuncId, Func, FuncState}}}, Timeout). --spec remove(Name, Func) -> 'ok' when +-spec remove(Name, Func | FuncId) -> 'ok' when Name :: name(), - Func :: dbg_fun(). -remove(Name, Func) -> - send_system_msg(Name, {debug, {remove, Func}}). + Func :: dbg_fun(), + FuncId :: term(). +remove(Name, FuncOrFuncId) -> + send_system_msg(Name, {debug, {remove, FuncOrFuncId}}). --spec remove(Name, Func, Timeout) -> 'ok' when +-spec remove(Name, Func | FuncId, Timeout) -> 'ok' when Name :: name(), Func :: dbg_fun(), + FuncId :: term(), Timeout :: timeout(). -remove(Name, Func, Timeout) -> - send_system_msg(Name, {debug, {remove, Func}}, Timeout). +remove(Name, FuncOrFuncId, Timeout) -> + send_system_msg(Name, {debug, {remove, FuncOrFuncId}}, Timeout). %%----------------------------------------------------------------- %% All system messages sent are on the form {system, From, Msg} @@ -387,6 +397,13 @@ handle_debug([{log_to_file, Fd} | T], FormFunc, State, Event) -> handle_debug([{statistics, StatData} | T], FormFunc, State, Event) -> NStatData = stat(Event, StatData), [{statistics, NStatData} | handle_debug(T, FormFunc, State, Event)]; +handle_debug([{FuncId, {Func, FuncState}} | T], FormFunc, State, Event) -> + case catch Func(FuncState, Event, State) of + done -> handle_debug(T, FormFunc, State, Event); + {'EXIT', _} -> handle_debug(T, FormFunc, State, Event); + NFuncState -> + [{FuncId, {Func, NFuncState}} | handle_debug(T, FormFunc, State, Event)] + end; handle_debug([{Func, FuncState} | T], FormFunc, State, Event) -> case catch Func(FuncState, Event, State) of done -> handle_debug(T, FormFunc, State, Event); @@ -544,8 +561,10 @@ debug_cmd(no_debug, Debug) -> {ok, []}; debug_cmd({install, {Func, FuncState}}, Debug) -> {ok, install_debug(Func, FuncState, Debug)}; -debug_cmd({remove, Func}, Debug) -> - {ok, remove_debug(Func, Debug)}; +debug_cmd({install, {FuncId, Func, FuncState}}, Debug) -> + {ok, install_debug(FuncId, {Func, FuncState}, Debug)}; +debug_cmd({remove, FuncOrFuncId}, Debug) -> + {ok, remove_debug(FuncOrFuncId, Debug)}; debug_cmd(_Unknown, Debug) -> {unknown_debug, Debug}. @@ -573,6 +592,7 @@ get_stat(_) -> stat({in, _Msg}, {Time, Reds, In, Out}) -> {Time, Reds, In+1, Out}; stat({in, _Msg, _From}, {Time, Reds, In, Out}) -> {Time, Reds, In+1, Out}; stat({out, _Msg, _To}, {Time, Reds, In, Out}) -> {Time, Reds, In, Out+1}; +stat({out, _Msg, _To, _State}, {Time, Reds, In, Out}) -> {Time, Reds, In, Out+1}; stat(_, StatData) -> StatData. trim(N, LogData) -> @@ -582,9 +602,9 @@ trim(N, LogData) -> %% Debug structure manipulating functions %%----------------------------------------------------------------- install_debug(Item, Data, Debug) -> - case get_debug2(Item, Debug, undefined) of - undefined -> [{Item, Data} | Debug]; - _ -> Debug + case lists:keysearch(Item, 1, Debug) of + false -> [{Item, Data} | Debug]; + _ -> Debug end. remove_debug(Item, Debug) -> lists:keydelete(Item, 1, Debug). @@ -635,7 +655,8 @@ close_log_file(Debug) -> | {'log_to_file', FileName} | {'install', FuncSpec}, FileName :: file:name(), - FuncSpec :: {Func, FuncState}, + FuncSpec :: {Func, FuncState} | {FuncId, Func, FuncState}, + FuncId :: term(), Func :: dbg_fun(), FuncState :: term(). debug_options(Options) -> @@ -658,6 +679,8 @@ debug_options([{log_to_file, FileName} | T], Debug) -> end; debug_options([{install, {Func, FuncState}} | T], Debug) -> debug_options(T, install_debug(Func, FuncState, Debug)); +debug_options([{install, {FuncId, Func, FuncState}} | T], Debug) -> + debug_options(T, install_debug(FuncId, {Func, FuncState}, Debug)); debug_options([_ | T], Debug) -> debug_options(T, Debug); debug_options([], Debug) -> |