Blob Blame History Raw
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Thu, 20 Aug 2015 09:44:43 +0200
Subject: [PATCH] Remove unused code in error logger handlers

A long time ago, errors from the emulator itself was sent as
messages that would end up in the handle_info/2 function.
Those clauses in handle_info/2 can be removed.

The code for handling events tagged 'info' instead of 'info_msg'
can also be taken out.

error_logger_file_h: Refactor and modernize code

Refactor, simplify, and modernize the code to facilitate future
improvements in the following commits.

Teach error_logger_file_h to truncate big messages

Add the possibility to truncate big messages to avoid running out
of memory.

error_logger_tty_h: Refactor and modernize code

Refactor, simplify, and modernize the code to facilitate future
improvements in the following commits.

Teach error_logger_tty_h to truncate big messages

Add the possibility to truncate big messages to avoid running out
of memory.

stdlib: Fix leaking files after error_logger:logfile(close)

Introduced when changing state from tuple to record.

Make the scanned form of the io_lib format strings available for processing

This adds three new functions to io_lib - scan_format/2, unscan_format/1,
and build_text/1 - which expose the parsed form of the format control
sequences to make it possible to easily modify or filter the input to
io_lib:format/2. This can e.g. be used in order to replace unbounded-size
control sequences like ~w or ~p with corresponding depth-limited ~W and ~P
before doing the actual formatting.

diff --git a/lib/stdlib/doc/src/io.xml b/lib/stdlib/doc/src/io.xml
index 90f24c4..6613dcd 100644
--- a/lib/stdlib/doc/src/io.xml
+++ b/lib/stdlib/doc/src/io.xml
@@ -505,7 +505,8 @@ ok
             <p>Writes the data with standard syntax in the same way as
               <c>~w</c>, but breaks terms whose printed representation
               is longer than one line into many lines and indents each
-              line sensibly. It also tries to detect lists of
+              line sensibly. Left justification is not supported.
+              It also tries to detect lists of
               printable characters and to output these as strings. The
               Unicode translation modifier is used for determining
               what characters are printable. For example:</p>
diff --git a/lib/stdlib/doc/src/io_lib.xml b/lib/stdlib/doc/src/io_lib.xml
index 68352ff..0c1c84d 100644
--- a/lib/stdlib/doc/src/io_lib.xml
+++ b/lib/stdlib/doc/src/io_lib.xml
@@ -4,7 +4,7 @@
 <erlref>
   <header>
     <copyright>
-      <year>1996</year><year>2013</year>
+      <year>1996</year><year>2014</year>
       <holder>Ericsson AB. All Rights Reserved.</holder>
     </copyright>
     <legalnotice>
@@ -59,6 +59,35 @@
     <datatype>
       <name name="latin1_string"/>
     </datatype>
+    <datatype>
+      <name name="format_spec"/>
+      <desc><p>Description:</p>
+      <list type="bulleted">
+        <item><p><c>control_char</c> is the type of control
+          sequence: <c>$P</c>, <c>$w</c>, and so on;</p>
+        </item>
+        <item><p><c>args</c> is a list of the arguments used by the
+          control sequence, or an empty list if the control sequence
+          does not take any arguments;</p>
+        </item>
+        <item><p><c>width</c> is the field width;</p>
+        </item>
+        <item><p><c>adjust</c> is the adjustment;</p>
+        </item>
+        <item><p><c>precision</c> is the precision of the printed
+          argument;</p>
+        </item>
+        <item><p><c>pad_char</c> is the padding character;</p>
+        </item>
+        <item><p><c>encoding</c> is set to <c>true</c> if the translation
+          modifier <c>t</c> is present;</p>
+        </item>
+        <item><p><c>strings</c> is set to <c>false</c> if the modifier
+          <c>l</c> is present.</p>
+        </item>
+      </list>
+      </desc>
+    </datatype>
   </datatypes>
   <funcs>
     <func>
@@ -260,6 +289,45 @@
       </desc>
     </func>
     <func>
+      <name name="scan_format" arity="2"/>
+      <fsummary>Parse all control sequences in the format string</fsummary>
+      <desc>
+        <p>Returns a list corresponding to the given format string,
+          where control sequences have been replaced with
+          corresponding tuples. This list can be passed to <seealso
+          marker="#build_text/1">io_lib:build_text/1</seealso> to have
+          the same effect as <c>io_lib:format(Format, Args)</c>, or to
+          <seealso
+          marker="#unscan_format/1">io_lib:unscan_format/1</seealso>
+          in order to get the corresponding pair of <c>Format</c> and
+          <c>Args</c> (with every <c>*</c> and corresponding argument
+          expanded to numeric values).</p>
+        <p>A typical use of this function is to replace unbounded-size
+          control sequences like <c>~w</c> and <c>~p</c> with the
+          depth-limited variants <c>~W</c> and <c>~P</c> before
+          formatting to text, e.g. in a logger.</p>
+      </desc>
+    </func>
+    <func>
+      <name name="unscan_format" arity="1"/>
+      <fsummary>Revert a pre-parsed format list to a plain character list
+                and a list of arguments</fsummary>
+      <desc>
+        <p>See <seealso
+          marker="#scan_format/2">io_lib:scan_format/2</seealso> for
+          details.</p>
+      </desc>
+    </func>
+    <func>
+      <name name="build_text" arity="1"/>
+      <fsummary>Build the output text for a pre-parsed format list</fsummary>
+      <desc>
+        <p>See <seealso
+          marker="#scan_format/2">io_lib:scan_format/2</seealso> for
+          details.</p>
+      </desc>
+    </func>
+    <func>
       <name name="indentation" arity="2"/>
       <fsummary>Indentation after printing string</fsummary>
       <desc>
diff --git a/lib/stdlib/src/error_logger_file_h.erl b/lib/stdlib/src/error_logger_file_h.erl
index e9364ed..ca44d01 100644
--- a/lib/stdlib/src/error_logger_file_h.erl
+++ b/lib/stdlib/src/error_logger_file_h.erl
@@ -23,24 +23,28 @@
 
 %%%
 %%% A handler that can be connected to the error_logger
-%%% event handler.
-%%% Writes all events formatted to file.
-%%%   Handles events tagged error, emulator and info.
+%%% event handler. Writes all events formatted to file.
 %%%
 %%% It can only be started from error_logger:swap_handler({logfile, File})
-%%% or error_logger:logfile(File)
+%%% or error_logger:logfile(File).
 %%%
 
 -export([init/1,
 	 handle_event/2, handle_call/2, handle_info/2,
 	 terminate/2, code_change/3]).
 
+-record(st,
+	{fd,
+	 filename,
+	 prev_handler,
+	 depth=unlimited :: 'unlimited' | non_neg_integer()}).
+
 %% This one is used when we takeover from the simple error_logger.
 init({File, {error_logger, Buf}}) ->
     case init(File, error_logger) of
-	{ok, {Fd, File, PrevHandler}} ->
-	    write_events(Fd, Buf),
-	    {ok, {Fd, File, PrevHandler}};
+	{ok, State} ->
+	    write_events(State, Buf),
+	    {ok, State};
 	Error ->
 	    Error
     end;
@@ -52,49 +56,45 @@ init(File, PrevHandler) ->
     process_flag(trap_exit, true),
     case file:open(File, [write]) of
 	{ok,Fd} ->
-	    {ok, {Fd, File, PrevHandler}};
+	    Depth = get_depth(),
+	    State = #st{fd=Fd,filename=File,prev_handler=PrevHandler,
+			depth=Depth},
+	    {ok, State};
 	Error ->
 	    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, {Fd, File, PrevHandler}) ->
-    write_event(Fd, tag_event(Event)),
-    {ok, {Fd, File, PrevHandler}};
-handle_event(_, State) ->
+handle_event(Event, State) ->
+    write_event(State, Event),
     {ok, State}.
 
-handle_info({'EXIT', Fd, _Reason}, {Fd, _File, PrevHandler}) ->
+handle_info({'EXIT', Fd, _Reason}, #st{fd=Fd,prev_handler=PrevHandler}) ->
     case PrevHandler of
 	[] ->
 	    remove_handler;
 	_ -> 
 	    {swap_handler, install_prev, [], PrevHandler, go_back}
     end;
-handle_info({emulator, GL, Chars}, {Fd, File, PrevHandler})
-  when node(GL) == node() ->
-    write_event(Fd, tag_event({emulator, GL, Chars})),
-    {ok, {Fd, File, PrevHandler}};
-handle_info({emulator, noproc, Chars}, {Fd, File, PrevHandler}) ->
-    write_event(Fd, tag_event({emulator, noproc, Chars})),
-    {ok, {Fd, File, PrevHandler}};
 handle_info(_, State) ->
     {ok, State}.
 
-handle_call(filename, {Fd, File, Prev}) ->
-    {ok, File, {Fd, File, Prev}};
+handle_call(filename, #st{filename=File}=State) ->
+    {ok, File, State};
 handle_call(_Query, State) ->
     {ok, {error, bad_query}, State}.
 
-terminate(_Reason, State) ->
-    case State of
-        {Fd, _File, _Prev} ->
-            ok = file:close(Fd);
-        _ ->
-            ok
-    end,
-    [].
+terminate(_Reason, #st{fd=Fd}) ->
+    file:close(Fd).
 
 code_change(_OldVsn, State, _Extra) ->
     {ok, State}.
@@ -103,69 +103,71 @@ code_change(_OldVsn, State, _Extra) ->
 %%% Misc. functions.
 %%% ------------------------------------------------------
 
-tag_event(Event) ->    
-    {erlang:universaltime(), Event}.
+write_events(State, [Ev|Es]) ->
+    %% Write the events in reversed order.
+    write_events(State, Es),
+    write_event(State, Ev);
+write_events(_State, []) ->
+    ok.
 
-write_events(Fd, Events) -> write_events1(Fd, lists:reverse(Events)).
+write_event(#st{fd=Fd}=State, Event) ->
+    case parse_event(Event) of
+	ignore ->
+	    ok;
+	{Head,Pid,FormatList} ->
+	    Time = maybe_utc(erlang:universaltime()),
+	    Header = write_time(Time, Head),
+	    Body = format_body(State, FormatList),
+	    AtNode = if
+			 node(Pid) =/= node() ->
+			     ["** at node ",atom_to_list(node(Pid))," **\n"];
+			 true ->
+			     []
+		     end,
+	    io:put_chars(Fd, [Header,Body,AtNode])
+    end.
 
-write_events1(Fd, [Event|Es]) ->
-    write_event(Fd, Event),
-    write_events1(Fd, Es);
-write_events1(_, []) ->
-    ok.
+format_body(State, [{Format,Args}|T]) ->
+    S = try format(State, Format, Args) of
+	    S0 ->
+		S0
+	catch
+	    _:_ ->
+		format(State, "ERROR: ~p - ~p\n", [Format,Args])
+	end,
+    [S|format_body(State, T)];
+format_body(_State, []) ->
+    [].
 
-write_event(Fd, {Time, {error, _GL, {Pid, Format, Args}}}) ->
-    T = write_time(maybe_utc(Time)),
-    case catch io_lib:format(add_node(Format,Pid), Args) of
-	S when is_list(S) ->
-	    io:format(Fd, T ++ S, []);
-	_ ->
-	    F = add_node("ERROR: ~p - ~p~n", Pid),
-	    io:format(Fd, T ++ F, [Format,Args])
-    end;
-write_event(Fd, {Time, {emulator, _GL, Chars}}) ->
-    T = write_time(maybe_utc(Time)),
-    case catch io_lib:format(Chars, []) of
-	S when is_list(S) ->
-	    io:format(Fd, T ++ S, []);
-	_ ->
-	    io:format(Fd, T ++ "ERROR: ~p ~n", [Chars])
-    end;
-write_event(Fd, {Time, {info, _GL, {Pid, Info, _}}}) ->
-    T = write_time(maybe_utc(Time)),
-    io:format(Fd, T ++ add_node("~p~n",Pid),[Info]);
-write_event(Fd, {Time, {error_report, _GL, {Pid, std_error, Rep}}}) ->
-    T = write_time(maybe_utc(Time)),
-    S = format_report(Rep),
-    io:format(Fd, T ++ S ++ add_node("", Pid), []);
-write_event(Fd, {Time, {info_report, _GL, {Pid, std_info, Rep}}}) ->
-    T = write_time(maybe_utc(Time), "INFO REPORT"),
-    S = format_report(Rep),
-    io:format(Fd, T ++ S ++ add_node("", Pid), []);
-write_event(Fd, {Time, {info_msg, _GL, {Pid, Format, Args}}}) ->
-    T = write_time(maybe_utc(Time), "INFO REPORT"),
-    case catch io_lib:format(add_node(Format,Pid), Args) of
-	S when is_list(S) ->
-	    io:format(Fd, T ++ S, []);
-	_ ->
-	    F = add_node("ERROR: ~p - ~p~n", Pid),
-	    io:format(Fd, T ++ F, [Format,Args])
-    end;
-write_event(Fd, {Time, {warning_report, _GL, {Pid, std_warning, Rep}}}) ->
-    T = write_time(maybe_utc(Time), "WARNING REPORT"),
-    S = format_report(Rep),
-    io:format(Fd, T ++ S ++ add_node("", Pid), []);
-write_event(Fd, {Time, {warning_msg, _GL, {Pid, Format, Args}}}) ->
-    T = write_time(maybe_utc(Time), "WARNING REPORT"),
-    case catch io_lib:format(add_node(Format,Pid), Args) of
-	S when is_list(S) ->
-	    io:format(Fd, T ++ S, []);
-	_ ->
-	    F = add_node("ERROR: ~p - ~p~n", Pid),
-	    io:format(Fd, T ++ F, [Format,Args])
-    end;
-write_event(_, _) ->
-    ok.
+format(#st{depth=unlimited}, Format, Args) ->
+    io_lib:format(Format, Args);
+format(#st{depth=Depth}, Format0, Args) ->
+    Format1 = io_lib:scan_format(Format0, Args),
+    Format = limit_format(Format1, Depth),
+    io_lib:build_text(Format).
+
+limit_format([{C0,As,F,Ad,P,Pad,Enc,Str}|T], Depth) when C0 =:= $p;
+						     C0 =:= $w ->
+    C = C0 - ($a - $A),				%To uppercase.
+    [{C,As++[Depth],F,Ad,P,Pad,Enc,Str}||limit_format(T, Depth)];
+limit_format([H|T], Depth) ->
+    [H|limit_format(T, Depth)];
+limit_format([], _) ->
+    [].
+
+parse_event({error, _GL, {Pid, Format, Args}}) ->
+    {"ERROR REPORT",Pid,[{Format,Args}]};
+parse_event({info_msg, _GL, {Pid, Format, Args}}) ->
+    {"INFO REPORT",Pid,[{Format, Args}]};
+parse_event({warning_msg, _GL, {Pid, Format, Args}}) ->
+    {"WARNING REPORT",Pid,[{Format,Args}]};
+parse_event({error_report, _GL, {Pid, std_error, Args}}) ->
+    {"ERROR REPORT",Pid,format_term(Args)};
+parse_event({info_report, _GL, {Pid, std_info, Args}}) ->
+    {"INFO REPORT",Pid,format_term(Args)};
+parse_event({warning_report, _GL, {Pid, std_warning, Args}}) ->
+    {"WARNING REPORT",Pid,format_term(Args)};
+parse_event(_) -> ignore.
 
 maybe_utc(Time) ->
     UTC = case application:get_env(sasl, utc_log) of
@@ -182,30 +184,27 @@ maybe_utc(Time) ->
 maybe_utc(Time, true) -> {utc, Time};
 maybe_utc(Time, _) -> {local, calendar:universal_time_to_local_time(Time)}.
 
-format_report(Rep) when is_list(Rep) ->
-    case string_p(Rep) of
+format_term(Term) when is_list(Term) ->
+    case string_p(Term) of
 	true ->
-	    io_lib:format("~s~n",[Rep]);
-	_ ->
-	    format_rep(Rep)
+	    [{"~s\n",[Term]}];
+	false ->
+	    format_term_list(Term)
     end;
-format_report(Rep) ->
-    io_lib:format("~p~n",[Rep]).
-
-format_rep([{Tag,Data}|Rep]) ->
-    io_lib:format("    ~p: ~p~n",[Tag,Data]) ++ format_rep(Rep);
-format_rep([Other|Rep]) ->
-    io_lib:format("    ~p~n",[Other]) ++ format_rep(Rep);
-format_rep(_) ->
+format_term(Term) ->
+    [{"~p\n",[Term]}].
+
+format_term_list([{Tag,Data}|T]) ->
+    [{"    ~p: ~p\n",[Tag,Data]}|format_term_list(T)];
+format_term_list([Data|T]) ->
+    [{"    ~p\n",[Data]}|format_term_list(T)];
+format_term_list([]) ->
+    [];
+format_term_list(_) ->
+    %% Continue to allow non-proper lists for now.
+    %% FIXME: Remove this clause in OTP 19.
     [].
 
-add_node(X, Pid) when is_atom(X) ->
-    add_node(atom_to_list(X), Pid);
-add_node(X, Pid) when node(Pid) =/= node() ->
-    lists:concat([X,"** at node ",node(Pid)," **~n"]);
-add_node(X, _) ->
-    X.
-
 string_p([]) ->
     false;
 string_p(Term) ->
@@ -221,15 +220,10 @@ string_p1([$\b|T]) -> string_p1(T);
 string_p1([$\f|T]) -> string_p1(T);
 string_p1([$\e|T]) -> string_p1(T);
 string_p1([H|T]) when is_list(H) ->
-    case string_p1(H) of
-	true -> string_p1(T);
-	_    -> false
-    end;
+    string_p1(H) andalso string_p1(T);
 string_p1([]) -> true;
 string_p1(_) ->  false.
 
-write_time(Time) -> write_time(Time, "ERROR REPORT").
-
 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)]);
diff --git a/lib/stdlib/src/error_logger_tty_h.erl b/lib/stdlib/src/error_logger_tty_h.erl
index ad5891f..72a052f 100644
--- a/lib/stdlib/src/error_logger_tty_h.erl
+++ b/lib/stdlib/src/error_logger_tty_h.erl
@@ -22,144 +22,178 @@
 
 %%%
 %%% A handler that can be connected to the error_logger
-%%% event handler.
-%%% Writes all events formatted to stdout.
-%%%   Handles events tagged error, emulator and info.
+%%% event handler. Writes all events formatted to stdout.
 %%%
 %%% It can only be started from error_logger:swap_handler(tty)
-%%% or error_logger:tty(true)
+%%% or error_logger:tty(true).
 %%%
 
 -export([init/1,
 	 handle_event/2, handle_call/2, handle_info/2,
 	 terminate/2, code_change/3]).
 
--export([write_event/2]).
+-export([write_event/2,write_event/3]).
+
+-record(st,
+	{user,
+	 prev_handler,
+	 io_mod=io,
+	 depth=unlimited}).
 
 %% This one is used when we takeover from the simple error_logger.
 init({[], {error_logger, Buf}}) ->
     User = set_group_leader(),
-    write_events(Buf,io),
-    {ok, {User, error_logger}};
+    Depth = get_depth(),
+    State = #st{user=User,prev_handler=error_logger,depth=Depth},
+    write_events(State, Buf),
+    {ok, State};
 %% This one is used if someone took over from us, and now wants to
 %% go back.
 init({[], {error_logger_tty_h, PrevHandler}}) ->
     User = set_group_leader(),
-    {ok, {User, PrevHandler}};
+    {ok, #st{user=User,prev_handler=PrevHandler}};
 %% This one is used when we are started directly.
 init([]) ->
     User = set_group_leader(),
-    {ok, {User, []}}.
+    Depth = get_depth(),
+    {ok, #st{user=User,prev_handler=[],depth=Depth}}.
+
+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) ->
-    write_event(tag_event(Event),io),
+    ok = do_write_event(State, tag_event(Event)),
     {ok, State}.
 
-handle_info({'EXIT', User, _Reason}, {User, PrevHandler}) ->
+handle_info({'EXIT', User, _Reason},
+	    #st{user=User,prev_handler=PrevHandler}=State) ->
     case PrevHandler of
 	[] ->
 	    remove_handler;
 	_ -> 
-	    {swap_handler, install_prev, {User, PrevHandler}, 
+	    {swap_handler, install_prev, State,
 	     PrevHandler, go_back}
     end;
-handle_info({emulator, GL, Chars}, State) when node(GL) == node() ->
-    write_event(tag_event({emulator, GL, Chars}),io),
-    {ok, State};
-handle_info({emulator, noproc, Chars}, State) ->
-    write_event(tag_event({emulator, noproc, Chars}),io),
-    {ok, State};
 handle_info(_, State) ->
     {ok, State}.
 
 handle_call(_Query, State) -> {ok, {error, bad_query}, State}.
 
-% unfortunately, we can't unlink from User - links are not counted!
-%    if pid(User) -> unlink(User); true -> ok end,
 terminate(install_prev, _State) ->
     [];
-terminate(_Reason, {_User, PrevHandler}) ->
+terminate(_Reason, #st{prev_handler=PrevHandler}) ->
     {error_logger_tty_h, PrevHandler}.
 
 code_change(_OldVsn, State, _Extra) ->
     {ok, State}.
 
+%% Exported (but unoffical) API.
+write_event(Event, IoMod) ->
+    do_write_event(#st{io_mod=IoMod}, Event).
+
+write_event(Event, IoMod, Depth) ->
+    do_write_event(#st{io_mod=IoMod,depth=Depth}, Event).
+
+
 %%% ------------------------------------------------------
 %%% Misc. functions.
 %%% ------------------------------------------------------
 
 set_group_leader() ->
     case whereis(user) of
-	User when is_pid(User) -> link(User), group_leader(User,self()), User;
-	_                      -> false
+	User when is_pid(User) ->
+	    link(User),
+	    group_leader(User,self()),
+	    User;
+	_ ->
+	    false
     end.
 
 tag_event(Event) ->    
     {erlang:universaltime(), Event}.
 
-write_events(Events,IOMod) -> write_events1(lists:reverse(Events),IOMod).
-
-write_events1([Event|Es],IOMod) ->
-    write_event(Event,IOMod),
-    write_events1(Es,IOMod);
-write_events1([],_IOMod) ->
+write_events(State, [Ev|Es]) ->
+    %% Write the events in reverse order.
+    _ = write_events(State, Es),
+    _ = do_write_event(State, Ev),
+    ok;
+write_events(_State, []) ->
     ok.
 
-write_event({Time, {error, _GL, {Pid, Format, Args}}},IOMod) ->
-    T = write_time(maybe_utc(Time)),
-    case catch io_lib:format(add_node(Format,Pid), Args) of
-	S when is_list(S) ->
-	    format(IOMod, T ++ S);
-	_ ->
-	    F = add_node("ERROR: ~p - ~p~n", Pid),
-	    format(IOMod, T ++ F, [Format,Args])
+do_write_event(State, {Time0, Event}) ->
+    case parse_event(Event) of
+	ignore ->
+	    ok;
+	{Head,Pid,FormatList} ->
+	    Time = maybe_utc(Time0),
+	    Header = write_time(Time, Head),
+	    Body = format_body(State, FormatList),
+	    AtNode = if
+			 node(Pid) =/= node() ->
+			     ["** at node ",atom_to_list(node(Pid))," **\n"];
+			 true ->
+			     []
+		     end,
+	    Str = [Header,Body,AtNode],
+	    case State#st.io_mod of
+		io_lib ->
+		    Str;
+		io ->
+		    io:put_chars(user, Str)
+	    end
     end;
-write_event({Time, {emulator, _GL, Chars}},IOMod) ->
-    T = write_time(maybe_utc(Time)),
-    case catch io_lib:format(Chars, []) of
-	S when is_list(S) ->
-	    format(IOMod, T ++ S);
-	_ ->
-	    format(IOMod, T ++ "ERROR: ~p ~n", [Chars])
-    end;
-write_event({Time, {info, _GL, {Pid, Info, _}}},IOMod) ->
-    T = write_time(maybe_utc(Time)),
-    format(IOMod, T ++ add_node("~p~n",Pid),[Info]);
-write_event({Time, {error_report, _GL, {Pid, std_error, Rep}}},IOMod) ->
-    T = write_time(maybe_utc(Time)),
-    S = format_report(Rep),
-    format(IOMod, T ++ S ++ add_node("", Pid));
-write_event({Time, {info_report, _GL, {Pid, std_info, Rep}}},IOMod) ->
-    T = write_time(maybe_utc(Time), "INFO REPORT"),
-    S = format_report(Rep),
-    format(IOMod, T ++ S ++ add_node("", Pid));
-write_event({Time, {info_msg, _GL, {Pid, Format, Args}}},IOMod) ->
-    T = write_time(maybe_utc(Time), "INFO REPORT"),
-    case catch io_lib:format(add_node(Format,Pid), Args) of
-	S when is_list(S) ->
-	    format(IOMod, T ++ S);
-	_ ->
-	    F = add_node("ERROR: ~p - ~p~n", Pid),
-	    format(IOMod, T ++ F, [Format,Args])
-    end;
-write_event({Time, {warning_report, _GL, {Pid, std_warning, Rep}}},IOMod) ->
-    T = write_time(maybe_utc(Time), "WARNING REPORT"),
-    S = format_report(Rep),
-    format(IOMod, T ++ S ++ add_node("", Pid));
-write_event({Time, {warning_msg, _GL, {Pid, Format, Args}}},IOMod) ->
-    T = write_time(maybe_utc(Time), "WARNING REPORT"),
-    case catch io_lib:format(add_node(Format,Pid), Args) of
-	S when is_list(S) ->
-	    format(IOMod, T ++ S);
-	_ ->
-	    F = add_node("ERROR: ~p - ~p~n", Pid),
-	    format(IOMod, T ++ F, [Format,Args])
-    end;
-write_event({_Time, _Error},_IOMod) ->
+do_write_event(_, _) ->
     ok.
 
+format_body(State, [{Format,Args}|T]) ->
+    S = try format(State, Format, Args) of
+	    S0 ->
+		S0
+	catch
+	    _:_ ->
+		format(State, "ERROR: ~p - ~p\n", [Format,Args])
+	end,
+    [S|format_body(State, T)];
+format_body(_State, []) ->
+    [].
+
+format(#st{depth=unlimited}, Format, Args) ->
+    io_lib:format(Format, Args);
+format(#st{depth=Depth}, Format0, Args) ->
+    Format1 = io_lib:scan_format(Format0, Args),
+    Format = limit_format(Format1, Depth),
+    io_lib:build_text(Format).
+
+limit_format([{C0,As,F,Ad,P,Pad,Enc,Str}|T], Depth) when C0 =:= $p;
+						     C0 =:= $w ->
+    C = C0 - ($a - $A),				%To uppercase.
+    [{C,As++[Depth],F,Ad,P,Pad,Enc,Str}|limit_format(T, Depth)];
+limit_format([H|T], Depth) ->
+    [H|limit_format(T, Depth)];
+limit_format([], _) ->
+    [].
+
+parse_event({error, _GL, {Pid, Format, Args}}) ->
+    {"ERROR REPORT",Pid,[{Format,Args}]};
+parse_event({info_msg, _GL, {Pid, Format, Args}}) ->
+    {"INFO REPORT",Pid,[{Format, Args}]};
+parse_event({warning_msg, _GL, {Pid, Format, Args}}) ->
+    {"WARNING REPORT",Pid,[{Format,Args}]};
+parse_event({error_report, _GL, {Pid, std_error, Args}}) ->
+    {"ERROR REPORT",Pid,format_term(Args)};
+parse_event({info_report, _GL, {Pid, std_info, Args}}) ->
+    {"INFO REPORT",Pid,format_term(Args)};
+parse_event({warning_report, _GL, {Pid, std_warning, Args}}) ->
+    {"WARNING REPORT",Pid,format_term(Args)};
+parse_event(_) -> ignore.
+
 maybe_utc(Time) ->
     UTC = case application:get_env(sasl, utc_log) of
               {ok, Val} -> Val;
@@ -175,33 +209,26 @@ maybe_utc(Time) ->
 maybe_utc(Time, true) -> {utc, Time};
 maybe_utc(Time, _) -> {local, calendar:universal_time_to_local_time(Time)}.
 
-format(IOMod, String)       -> format(IOMod, String, []).
-format(io_lib, String, Args) -> io_lib:format(String, Args);
-format(io, String, Args) -> io:format(user, String, Args).
-
-format_report(Rep) when is_list(Rep) ->
-    case string_p(Rep) of
+format_term(Term) when is_list(Term) ->
+    case string_p(Term) of
 	true ->
-	    io_lib:format("~s~n",[Rep]);
-	_ ->
-	    format_rep(Rep)
+	    [{"~s\n",[Term]}];
+	false ->
+	    format_term_list(Term)
     end;
-format_report(Rep) ->
-    io_lib:format("~p~n",[Rep]).
-
-format_rep([{Tag,Data}|Rep]) ->
-    io_lib:format("    ~p: ~p~n",[Tag,Data]) ++ format_rep(Rep);
-format_rep([Other|Rep]) ->
-    io_lib:format("    ~p~n",[Other]) ++ format_rep(Rep);
-format_rep(_) ->
-    [].
+format_term(Term) ->
+    [{"~p\n",[Term]}].
 
-add_node(X, Pid) when is_atom(X) ->
-    add_node(atom_to_list(X), Pid);
-add_node(X, Pid) when node(Pid) =/= node() ->
-    lists:concat([X,"** at node ",node(Pid)," **~n"]);
-add_node(X, _) ->
-    X.
+format_term_list([{Tag,Data}|T]) ->
+    [{"    ~p: ~p\n",[Tag,Data]}|format_term_list(T)];
+format_term_list([Data|T]) ->
+    [{"    ~p\n",[Data]}|format_term_list(T)];
+format_term_list([]) ->
+    [];
+format_term_list(_) ->
+    %% Continue to allow non-proper lists for now.
+    %% FIXME: Remove this clause in OTP 19.
+    [].
 
 string_p([]) ->
     false;
@@ -225,7 +252,6 @@ string_p1([H|T]) when is_list(H) ->
 string_p1([]) -> true;
 string_p1(_) ->  false.
 
-write_time(Time) -> write_time(Time, "ERROR REPORT").
 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)]);
diff --git a/lib/stdlib/src/io_lib.erl b/lib/stdlib/src/io_lib.erl
index 9e69601..3c173dc 100644
--- a/lib/stdlib/src/io_lib.erl
+++ b/lib/stdlib/src/io_lib.erl
@@ -2,7 +2,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 1996-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2014. All Rights Reserved.
 %%
 %% The contents of this file are subject to the Erlang Public License,
 %% Version 1.1, (the "License"); you may not use this file except in
@@ -61,6 +61,7 @@
 -module(io_lib).
 
 -export([fwrite/2,fread/2,fread/3,format/2]).
+-export([scan_format/2,unscan_format/1,build_text/1]).
 -export([print/1,print/4,indentation/2]).
 
 -export([write/1,write/2,write/3,nl/0,format_prompt/1,format_prompt/2]).
@@ -84,7 +85,7 @@
          deep_unicode_char_list/1]).
 
 -export_type([chars/0, latin1_string/0, continuation/0,
-              fread_error/0, fread_item/0]).
+              fread_error/0, fread_item/0, format_spec/0]).
 
 %%----------------------------------------------------------------------
 
@@ -109,6 +110,18 @@
 
 -type fread_item() :: string() | atom() | integer() | float().
 
+-type format_spec() ::
+        {
+	   ControlChar :: char(),
+           Args        :: [any()],
+           Width       :: 'none' | integer(),
+           Adjust      :: 'left' | 'right',
+           Precision   :: 'none' | integer(),
+           PadChar     :: char(),
+           Encoding    :: 'unicode' | 'latin1',
+           Strings     :: boolean()
+         }.
+
 %%----------------------------------------------------------------------
 
 %% Interface calls to sub-modules.
@@ -157,6 +170,31 @@ format(Format, Args) ->
 	    Other
     end.
 
+-spec scan_format(Format, Data) -> FormatList when
+      Format :: io:format(),
+      Data :: [term()],
+      FormatList :: [char() | format_spec()].
+
+scan_format(Format, Args) ->
+    try io_lib_format:scan(Format, Args)
+    catch
+        _:_ -> erlang:error(badarg, [Format, Args])
+    end.
+
+-spec unscan_format(FormatList) -> {Format, Data} when
+      FormatList :: [char() | format_spec()],
+      Format :: io:format(),
+      Data :: [term()].
+
+unscan_format(FormatList) ->
+    io_lib_format:unscan(FormatList).
+
+-spec build_text(FormatList) -> chars() when
+      FormatList :: [char() | format_spec()].
+
+build_text(FormatList) ->
+    io_lib_format:build(FormatList).
+
 -spec print(Term) -> chars() when
       Term :: term().
 
diff --git a/lib/stdlib/src/io_lib_format.erl b/lib/stdlib/src/io_lib_format.erl
index 56e15a1..37b47d7 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-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2014. All Rights Reserved.
 %% 
 %% The contents of this file are subject to the Erlang Public License,
 %% Version 1.1, (the "License"); you may not use this file except in
@@ -20,10 +20,9 @@
 
 %% Formatting functions of io library.
 
--export([fwrite/2,fwrite_g/1,indentation/2]).
+-export([fwrite/2,fwrite_g/1,indentation/2,scan/2,unscan/1,build/1]).
 
-%% fwrite(Format, ArgList) -> string().
-%%  Format the arguments in ArgList after string Format. Just generate
+%%  Format the arguments in Args after string Format. Just generate
 %%  an error if there is an error in the arguments.
 %%
 %%  To do the printing command correctly we need to calculate the
@@ -37,15 +36,83 @@
 %%  and it also splits the handling of the control characters into two
 %%  parts.
 
-fwrite(Format, Args) when is_atom(Format) ->
-    fwrite(atom_to_list(Format), Args);
-fwrite(Format, Args) when is_binary(Format) ->
-    fwrite(binary_to_list(Format), Args);
+-spec fwrite(Format, Data) -> FormatList when
+      Format :: io:format(),
+      Data :: [term()],
+      FormatList :: [char() | io_lib:format_spec()].
+
 fwrite(Format, Args) ->
-    Cs = collect(Format, Args),
+    build(scan(Format, Args)).
+
+%% 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).
 
+%% Parse all control sequences in the format string.
+
+-spec scan(Format, Data) -> FormatList when
+      Format :: io:format(),
+      Data :: [term()],
+      FormatList :: [char() | io_lib:format_spec()].
+
+scan(Format, Args) when is_atom(Format) ->
+    scan(atom_to_list(Format), Args);
+scan(Format, Args) when is_binary(Format) ->
+    scan(binary_to_list(Format), Args);
+scan(Format, Args) ->
+    collect(Format, Args).
+
+%% Revert a pre-parsed format list to a plain character list and a
+%% list of arguments.
+
+-spec unscan(FormatList) -> {Format, Data} when
+      FormatList :: [char() | io_lib:format_spec()],
+      Format :: io:format(),
+      Data :: [term()].
+
+unscan(Cs) ->
+    {print(Cs), args(Cs)}.
+
+args([{_C,As,_F,_Ad,_P,_Pad,_Enc,_Str} | Cs]) ->
+    As ++ args(Cs);
+args([_C | Cs]) ->
+    args(Cs);
+args([]) ->
+    [].
+
+print([{C,_As,F,Ad,P,Pad,Enc,Str} | Cs ]) ->
+    print(C, F, Ad, P, Pad, Enc, Str) ++ print(Cs);
+print([C | Cs]) ->
+    [C | print(Cs)];
+print([]) ->
+    [].
+
+print(C, F, Ad, P, Pad, Encoding, Strings) ->
+    [$~] ++ print_field_width(F, Ad) ++ print_precision(P) ++
+        print_pad_char(Pad) ++ print_encoding(Encoding) ++
+        print_strings(Strings) ++ [C].
+
+print_field_width(none, _Ad) -> "";
+print_field_width(F, left) -> integer_to_list(-F);
+print_field_width(F, right) -> integer_to_list(F).
+
+print_precision(none) -> "";
+print_precision(P) -> [$. | integer_to_list(P)].
+
+print_pad_char($\s) -> ""; % default, no need to make explicit
+print_pad_char(Pad) -> [$., Pad].
+
+print_encoding(unicode) -> "t";
+print_encoding(latin1) -> "".
+
+print_strings(false) -> "l";
+print_strings(true) -> "".
+
 collect([$~|Fmt0], Args0) ->
     {C,Fmt1,Args1} = collect_cseq(Fmt0, Args0),
     [C|collect(Fmt1, Args1)];
@@ -141,7 +208,7 @@ pcount([{$P,_As,_F,_Ad,_P,_Pad,_Enc,_Str}|Cs], Acc) -> pcount(Cs, Acc+1);
 pcount([_|Cs], Acc) -> pcount(Cs, Acc);
 pcount([], Acc) -> Acc.
 
-%% build([Control], Pc, Indentation) -> string().
+%% build([Control], Pc, Indentation) -> io_lib:chars().
 %%  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.
@@ -162,10 +229,14 @@ decr_pc($p, Pc) -> Pc - 1;
 decr_pc($P, Pc) -> Pc - 1;
 decr_pc(_, Pc) -> Pc.
 
-%% indentation(String, Indentation) -> Indentation.
+
 %%  Calculate the indentation of the end of a string given its start
 %%  indentation. We assume tabs at 8 cols.
 
+-spec indentation(String, StartIndent) -> integer() when
+      String :: io_lib:chars(),
+      StartIndent :: integer().
+
 indentation([$\n|Cs], _I) -> indentation(Cs, 0);
 indentation([$\t|Cs], I) -> indentation(Cs, ((I + 8) div 8) * 8);
 indentation([C|Cs], I) when is_integer(C) ->
@@ -366,7 +437,6 @@ float_data([D|Cs], Ds) when D >= $0, D =< $9 ->
 float_data([_|Cs], Ds) ->
     float_data(Cs, Ds).
 
-%% fwrite_g(Float)
 %%  Writes the shortest, correctly rounded string that converts
 %%  to Float when read back with list_to_float/1.
 %%
@@ -374,6 +444,8 @@ float_data([_|Cs], Ds) ->
 %%  in Proceedings of the SIGPLAN '96 Conference on Programming
 %%  Language Design and Implementation.
 
+-spec fwrite_g(float()) -> string().
+
 fwrite_g(0.0) ->
     "0.0";
 fwrite_g(Float) when is_float(Float) ->
@@ -642,7 +714,7 @@ prefixed_integer(Int, F, Adj, Base, Pad, Prefix, Lowercase)
 	    term([Prefix|S], F, Adj, none, Pad)
     end.
 
-%% char(Char, Field, Adjust, Precision, PadChar) -> string().
+%% char(Char, Field, Adjust, Precision, PadChar) -> chars().
 
 char(C, none, _Adj, none, _Pad) -> [C];
 char(C, F, _Adj, none, _Pad) -> chars(C, F);