aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/error_logger_file_h.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src/error_logger_file_h.erl')
-rw-r--r--lib/stdlib/src/error_logger_file_h.erl103
1 files changed, 38 insertions, 65 deletions
diff --git a/lib/stdlib/src/error_logger_file_h.erl b/lib/stdlib/src/error_logger_file_h.erl
index 665685d3ee..58da0cbdd6 100644
--- a/lib/stdlib/src/error_logger_file_h.erl
+++ b/lib/stdlib/src/error_logger_file_h.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2016. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2017. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -55,9 +55,9 @@ init(File) ->
init(File, PrevHandler) ->
process_flag(trap_exit, true),
- case file:open(File, [write]) of
+ case file:open(File, [write,{encoding,utf8}]) of
{ok,Fd} ->
- Depth = get_depth(),
+ Depth = error_logger:get_format_depth(),
State = #st{fd=Fd,filename=File,prev_handler=PrevHandler,
depth=Depth},
{ok, State};
@@ -65,14 +65,6 @@ init(File, PrevHandler) ->
Error
end.
-get_depth() ->
- case application:get_env(kernel, error_logger_format_depth) of
- {ok, Depth} when is_integer(Depth) ->
- max(10, Depth);
- undefined ->
- unlimited
- end.
-
handle_event({_Type, GL, _Msg}, State) when node(GL) =/= node() ->
{ok, State};
handle_event(Event, State) ->
@@ -116,8 +108,8 @@ write_event(#st{fd=Fd}=State, Event) ->
ignore ->
ok;
{Head,Pid,FormatList} ->
- Time = maybe_utc(erlang:universaltime()),
- Header = write_time(Time, Head),
+ Time = erlang:universaltime(),
+ Header = header(Time, Head),
Body = format_body(State, FormatList),
AtNode = if
node(Pid) =/= node() ->
@@ -125,7 +117,7 @@ write_event(#st{fd=Fd}=State, Event) ->
true ->
[]
end,
- io:put_chars(Fd, [Header,Body,AtNode])
+ io:put_chars(Fd, [Header,AtNode,Body])
end.
format_body(State, [{Format,Args}|T]) ->
@@ -134,7 +126,7 @@ format_body(State, [{Format,Args}|T]) ->
S0
catch
_:_ ->
- format(State, "ERROR: ~p - ~p\n", [Format,Args])
+ format(State, "ERROR: ~tp - ~tp\n", [Format,Args])
end,
[S|format_body(State, T)];
format_body(_State, []) ->
@@ -172,72 +164,55 @@ parse_event({warning_report, _GL, {Pid, std_warning, Args}}) ->
{"WARNING REPORT",Pid,format_term(Args)};
parse_event(_) -> ignore.
-maybe_utc(Time) ->
- UTC = case application:get_env(sasl, utc_log) of
- {ok, Val} -> Val;
- undefined ->
- %% Backwards compatible:
- case application:get_env(stdlib, utc_log) of
- {ok, Val} -> Val;
- undefined -> false
- end
- end,
- maybe_utc(Time, UTC).
-
-maybe_utc(Time, true) -> {utc, Time};
-maybe_utc(Time, _) -> {local, calendar:universal_time_to_local_time(Time)}.
-
format_term(Term) when is_list(Term) ->
- case string_p(Term) of
+ case string_p(lists:flatten(Term)) of
true ->
- [{"~s\n",[Term]}];
+ [{"~ts\n",[Term]}];
false ->
format_term_list(Term)
end;
format_term(Term) ->
- [{"~p\n",[Term]}].
+ [{"~tp\n",[Term]}].
format_term_list([{Tag,Data}|T]) ->
- [{" ~p: ~p\n",[Tag,Data]}|format_term_list(T)];
+ [{" ~tp: ~tp\n",[Tag,Data]}|format_term_list(T)];
format_term_list([Data|T]) ->
- [{" ~p\n",[Data]}|format_term_list(T)];
+ [{" ~tp\n",[Data]}|format_term_list(T)];
format_term_list([]) ->
- [];
-format_term_list(_) ->
- %% Continue to allow non-proper lists for now.
- %% FIXME: Remove this clause in OTP 19.
[].
string_p([]) ->
false;
-string_p(Term) ->
- string_p1(Term).
+string_p(FlatList) ->
+ io_lib:printable_list(FlatList).
+
+get_utc_config() ->
+ %% SASL utc_log configuration overrides stdlib config
+ %% in order to have uniform timestamps in log messages
+ case application:get_env(sasl, utc_log) of
+ {ok, Val} -> Val;
+ undefined ->
+ case application:get_env(stdlib, utc_log) of
+ {ok, Val} -> Val;
+ undefined -> false
+ end
+ end.
-string_p1([H|T]) when is_integer(H), H >= $\s, H < 255 ->
- string_p1(T);
-string_p1([$\n|T]) -> string_p1(T);
-string_p1([$\r|T]) -> string_p1(T);
-string_p1([$\t|T]) -> string_p1(T);
-string_p1([$\v|T]) -> string_p1(T);
-string_p1([$\b|T]) -> string_p1(T);
-string_p1([$\f|T]) -> string_p1(T);
-string_p1([$\e|T]) -> string_p1(T);
-string_p1([H|T]) when is_list(H) ->
- string_p1(H) andalso string_p1(T);
-string_p1([]) -> true;
-string_p1(_) -> false.
+header(Time, Title) ->
+ case get_utc_config() of
+ true ->
+ header(Time, Title, "UTC ");
+ _ ->
+ header(calendar:universal_time_to_local_time(Time), Title, "")
+ end.
-write_time({utc,{{Y,Mo,D},{H,Mi,S}}}, Type) ->
- io_lib:format("~n=~s==== ~p-~s-~p::~s:~s:~s UTC ===~n",
- [Type,D,month(Mo),Y,t(H),t(Mi),t(S)]);
-write_time({local, {{Y,Mo,D},{H,Mi,S}}}, Type) ->
- io_lib:format("~n=~s==== ~p-~s-~p::~s:~s:~s ===~n",
- [Type,D,month(Mo),Y,t(H),t(Mi),t(S)]).
+header({{Y,Mo,D},{H,Mi,S}}, Title, UTC) ->
+ io_lib:format("~n=~ts==== ~p-~s-~p::~s:~s:~s ~s===~n",
+ [Title,D,month(Mo),Y,t(H),t(Mi),t(S),UTC]).
t(X) when is_integer(X) ->
- t1(integer_to_list(X));
-t(_) ->
- "".
+ t1(integer_to_list(X)).
+
t1([X]) -> [$0,X];
t1(X) -> X.
@@ -253,5 +228,3 @@ month(9) -> "Sep";
month(10) -> "Oct";
month(11) -> "Nov";
month(12) -> "Dec".
-
-