Skip to content

Commit

Permalink
Increase depth of error messages in Eunit Surefire reports
Browse files Browse the repository at this point in the history
Currently, error messages in Eunit Surefire reports are shortened just
like when written to a terminal.  However, the space limitations that
constrain terminal output do not apply here, so it's more useful to
include more of the error message.  Getting the full error message can
be particularly helpful when an assertMatch fails because of a long
and deep error term.

The new depth of 100 should be enough for most cases, while protecting
against runaway errors.
  • Loading branch information
legoscia committed Apr 7, 2011
1 parent d8dcd70 commit b6decaf
Show file tree
Hide file tree
Showing 2 changed files with 12 additions and 10 deletions.
18 changes: 10 additions & 8 deletions lib/eunit/src/eunit_lib.erl
Expand Up @@ -33,7 +33,7 @@
-export([dlist_next/1, uniq/1, fun_parent/1, is_string/1, command/1,
command/2, command/3, trie_new/0, trie_store/2, trie_match/2,
split_node/1, consult_file/1, list_dir/1, format_exit_term/1,
format_exception/1, format_error/1]).
format_exception/1, format_exception/2, format_error/1]).


%% Type definitions for describing exceptions
Expand All @@ -55,21 +55,23 @@

%% ---------------------------------------------------------------------
%% Formatting of error descriptors
format_exception(Exception) ->
format_exception(Exception, 20).

format_exception({Class,Term,Trace})
format_exception({Class,Term,Trace}, Depth)
when is_atom(Class), is_list(Trace) ->
case is_stacktrace(Trace) of
true ->
io_lib:format("~w:~P\n~s",
[Class, Term, 20, format_stacktrace(Trace)]);
[Class, Term, Depth, format_stacktrace(Trace)]);
false ->
format_term(Term)
format_term(Term, Depth)
end;
format_exception(Term) ->
format_term(Term).
format_exception(Term, Depth) ->
format_term(Term, Depth).

format_term(Term) ->
io_lib:format("~P\n", [Term, 15]).
format_term(Term, Depth) ->
io_lib:format("~P\n", [Term, Depth]).

format_exit_term(Term) ->
{Reason, Trace} = analyze_exit_term(Term),
Expand Down
4 changes: 2 additions & 2 deletions lib/eunit/src/eunit_surefire.erl
Expand Up @@ -323,15 +323,15 @@ write_testcase(
format_testcase_result(ok) -> [<<>>];
format_testcase_result({failed, {error, {Type, _}, _} = Exception}) when is_atom(Type) ->
[?INDENT, ?INDENT, <<"<failure type=\"">>, escape_attr(atom_to_list(Type)), <<"\">">>, ?NEWLINE,
<<"::">>, escape_text(eunit_lib:format_exception(Exception)),
<<"::">>, escape_text(eunit_lib:format_exception(Exception, 100)),
?INDENT, ?INDENT, <<"</failure>">>, ?NEWLINE];
format_testcase_result({failed, Term}) ->
[?INDENT, ?INDENT, <<"<failure type=\"unknown\">">>, ?NEWLINE,
escape_text(io_lib:write(Term)),
?INDENT, ?INDENT, <<"</failure>">>, ?NEWLINE];
format_testcase_result({aborted, {Class, _Term, _Trace} = Exception}) when is_atom(Class) ->
[?INDENT, ?INDENT, <<"<error type=\"">>, escape_attr(atom_to_list(Class)), <<"\">">>, ?NEWLINE,
<<"::">>, escape_text(eunit_lib:format_exception(Exception)),
<<"::">>, escape_text(eunit_lib:format_exception(Exception, 100)),
?INDENT, ?INDENT, <<"</error>">>, ?NEWLINE];
format_testcase_result({aborted, Term}) ->
[?INDENT, ?INDENT, <<"<error type=\"unknown\">">>, ?NEWLINE,
Expand Down

0 comments on commit b6decaf

Please sign in to comment.