~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/eunit/src/eunit_surefire.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
13
13
%% Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307
14
14
%% USA
15
15
%%
16
 
%% $Id: $
17
 
%%
18
 
%% @author Micka&euml;l R&eacute;mond <mremond@process-one.net>
 
16
%% @author Micka�l R�mond <mickael.remond@process-one.net>
19
17
%% @copyright 2009 Micka�l R�mond, Paul Guyot
20
18
%% @see eunit
21
19
%% @doc Surefire reports for EUnit (Format used by Maven and Atlassian
58
56
        {
59
57
          name :: chars(),
60
58
          description :: chars(),
61
 
          result :: ok | {failed, tuple()} | {aborted, tuple()} | {skipped, tuple()},
 
59
          result :: ok | {failed, tuple()} | {aborted, tuple()} | {skipped, term()},
62
60
          time :: integer(),
63
61
          output :: binary()
64
62
         }).
65
63
-record(testsuite,
66
64
        {
 
65
          id = 0 :: integer(),
67
66
          name = <<>> :: binary(),
68
67
          time = 0 :: integer(),
69
68
          output = <<>> :: binary(),
76
75
-record(state, {verbose = false,
77
76
                indent = 0,
78
77
                xmldir = ".",
79
 
                testsuite = #testsuite{}
 
78
                testsuites = [] :: [#testsuite{}]
80
79
               }).
81
80
 
82
81
start() ->
89
88
    XMLDir = proplists:get_value(dir, Options, ?XMLDIR),
90
89
    St = #state{verbose = proplists:get_bool(verbose, Options),
91
90
                xmldir = XMLDir,
92
 
                testsuite = #testsuite{}},
 
91
                testsuites = []},
93
92
    receive
94
93
        {start, _Reference} ->
95
94
            St
96
95
    end.
97
96
 
98
97
terminate({ok, _Data}, St) ->
99
 
    TestSuite = St#state.testsuite,
 
98
    TestSuites = St#state.testsuites,
100
99
    XmlDir = St#state.xmldir,
101
 
    write_report(TestSuite, XmlDir),
 
100
    write_reports(TestSuites, XmlDir),
102
101
    ok;
103
 
terminate({error, Reason}, _St) ->
104
 
    io:fwrite("Internal error: ~P.\n", [Reason, 25]),
105
 
    sync_end(error).
106
 
 
107
 
sync_end(Result) ->
108
 
    receive
109
 
        {stop, Reference, ReplyTo} ->
110
 
            ReplyTo ! {result, Reference, Result},
111
 
            ok
112
 
    end.
113
 
 
114
 
handle_begin(group, Data, St) ->
 
102
terminate({error, _Reason}, _St) ->
 
103
    %% Don't report any errors here, since eunit_tty takes care of that.
 
104
    %% Just terminate.
 
105
    ok.
 
106
 
 
107
handle_begin(Kind, Data, St) when Kind == group; Kind == test ->
 
108
    %% Run this code both for groups and tests; test is a bit
 
109
    %% surprising: This is a workaround for the fact that we don't get
 
110
    %% a group (handle_begin(group, ...) for testsuites (modules)
 
111
    %% which only have one test case.  In that case we get a test case
 
112
    %% with an id comprised of just one integer - the group id.
115
113
    NewId = proplists:get_value(id, Data),
116
114
    case NewId of
117
115
        [] ->
118
116
            St;
119
 
        [_GroupId] ->
 
117
        [GroupId] ->
120
118
            Desc = proplists:get_value(desc, Data),
121
 
            TestSuite = St#state.testsuite,
122
 
            NewTestSuite = TestSuite#testsuite{name = Desc},
123
 
            St#state{testsuite=NewTestSuite};
 
119
            TestSuite = #testsuite{id = GroupId, name = Desc},
 
120
            St#state{testsuites=store_suite(TestSuite, St#state.testsuites)};
124
121
        %% Surefire format is not hierarchic: Ignore subgroups:
125
122
        _ ->
126
123
            St
127
 
    end;
128
 
handle_begin(test, _Data, St) ->
129
 
    St.
 
124
    end.
130
125
handle_end(group, Data, St) ->
131
126
    %% Retrieve existing test suite:
132
127
    case proplists:get_value(id, Data) of
133
128
        [] ->
134
129
            St;
135
 
        [_GroupId|_] ->
136
 
            TestSuite = St#state.testsuite,
 
130
        [GroupId|_] ->
 
131
            TestSuites = St#state.testsuites,
 
132
            TestSuite = lookup_suite_by_group_id(GroupId, TestSuites),
137
133
 
138
134
            %% Update TestSuite data:
139
135
            Time = proplists:get_value(time, Data),
140
136
            Output = proplists:get_value(output, Data),
141
137
            NewTestSuite = TestSuite#testsuite{ time = Time, output = Output },
142
 
            St#state{testsuite=NewTestSuite}
 
138
            St#state{testsuites=store_suite(NewTestSuite, TestSuites)}
143
139
    end;
144
140
handle_end(test, Data, St) ->
145
141
    %% Retrieve existing test suite:
146
 
    TestSuite = St#state.testsuite,
 
142
    [GroupId|_] = proplists:get_value(id, Data),
 
143
    TestSuites = St#state.testsuites,
 
144
    TestSuite = lookup_suite_by_group_id(GroupId, TestSuites),
147
145
 
148
146
    %% Create test case:
149
147
    Name = format_name(proplists:get_value(source, Data),
155
153
    TestCase = #testcase{name = Name, description = Desc,
156
154
                         time = Time,output = Output},
157
155
    NewTestSuite = add_testcase_to_testsuite(Result, TestCase, TestSuite),
158
 
    St#state{testsuite=NewTestSuite}.
 
156
    St#state{testsuites=store_suite(NewTestSuite, TestSuites)}.
159
157
 
160
158
%% Cancel group does not give information on the individual cancelled test case
161
159
%% We ignore this event
163
161
    St;
164
162
handle_cancel(test, Data, St) ->
165
163
    %% Retrieve existing test suite:
166
 
    TestSuite = St#state.testsuite,
 
164
    [GroupId|_] = proplists:get_value(id, Data),
 
165
    TestSuites = St#state.testsuites,
 
166
    TestSuite = lookup_suite_by_group_id(GroupId, TestSuites),
167
167
 
168
168
    %% Create test case:
169
169
    Name = format_name(proplists:get_value(source, Data),
177
177
    NewTestSuite = TestSuite#testsuite{
178
178
                     skipped = TestSuite#testsuite.skipped+1,
179
179
                     testcases=[TestCase|TestSuite#testsuite.testcases] },
180
 
    St#state{testsuite=NewTestSuite}.
 
180
    St#state{testsuites=store_suite(NewTestSuite, TestSuites)}.
181
181
 
182
182
format_name({Module, Function, Arity}, Line) ->
183
183
    lists:flatten([atom_to_list(Module), ":", atom_to_list(Function), "/",
189
189
format_desc(Desc) when is_list(Desc) ->
190
190
    Desc.
191
191
 
 
192
lookup_suite_by_group_id(GroupId, TestSuites) ->
 
193
    #testsuite{} = lists:keyfind(GroupId, #testsuite.id, TestSuites).
 
194
 
 
195
store_suite(#testsuite{id=GroupId} = TestSuite, TestSuites) ->
 
196
    lists:keystore(GroupId, #testsuite.id, TestSuites, TestSuite).
 
197
 
192
198
%% Add testcase to testsuite depending on the result of the test.
193
199
add_testcase_to_testsuite(ok, TestCaseTmp, TestSuite) ->
194
200
    TestCase = TestCaseTmp#testcase{ result = ok },
220
226
%% Write a report to the XML directory.
221
227
%% This function opens the report file, calls write_report_to/2 and closes the file.
222
228
%% ----------------------------------------------------------------------------
 
229
write_reports(TestSuites, XmlDir) ->
 
230
    lists:foreach(fun(TestSuite) -> write_report(TestSuite, XmlDir) end,
 
231
                  TestSuites).
 
232
 
223
233
write_report(#testsuite{name = Name} = TestSuite, XmlDir) ->
224
234
    Filename = filename:join(XmlDir, lists:flatten(["TEST-", escape_suitename(Name)], ".xml")),
225
235
    case file:open(Filename, [write, raw]) of
299
309
            output = Output},
300
310
        FileDescriptor) ->
301
311
    DescriptionAttr = case Description of
302
 
                          <<>> -> [];
303
312
                          [] -> [];
304
313
                          _ -> [<<" description=\"">>, escape_attr(Description), <<"\"">>]
305
314
                      end,
308
317
        <<"\" name=\"">>, escape_attr(Name), <<"\"">>,
309
318
        DescriptionAttr],
310
319
    ContentAndEndTag = case {Result, Output} of
311
 
        {ok, []} -> [<<"/>">>, ?NEWLINE];
312
320
        {ok, <<>>} -> [<<"/>">>, ?NEWLINE];
313
321
        _ -> [<<">">>, ?NEWLINE, format_testcase_result(Result), format_testcase_output(Output), ?INDENT, <<"</testcase>">>, ?NEWLINE]
314
322
    end,
323
331
format_testcase_result(ok) -> [<<>>];
324
332
format_testcase_result({failed, {error, {Type, _}, _} = Exception}) when is_atom(Type) ->
325
333
    [?INDENT, ?INDENT, <<"<failure type=\"">>, escape_attr(atom_to_list(Type)), <<"\">">>, ?NEWLINE,
326
 
    <<"::">>, escape_text(eunit_lib:format_exception(Exception)),
 
334
    <<"::">>, escape_text(eunit_lib:format_exception(Exception, 100)),
327
335
    ?INDENT, ?INDENT, <<"</failure>">>, ?NEWLINE];
328
336
format_testcase_result({failed, Term}) ->
329
337
    [?INDENT, ?INDENT, <<"<failure type=\"unknown\">">>, ?NEWLINE,
331
339
    ?INDENT, ?INDENT, <<"</failure>">>, ?NEWLINE];
332
340
format_testcase_result({aborted, {Class, _Term, _Trace} = Exception}) when is_atom(Class) ->
333
341
    [?INDENT, ?INDENT, <<"<error type=\"">>, escape_attr(atom_to_list(Class)), <<"\">">>, ?NEWLINE,
334
 
    <<"::">>, escape_text(eunit_lib:format_exception(Exception)),
 
342
    <<"::">>, escape_text(eunit_lib:format_exception(Exception, 100)),
335
343
    ?INDENT, ?INDENT, <<"</error>">>, ?NEWLINE];
336
344
format_testcase_result({aborted, Term}) ->
337
345
    [?INDENT, ?INDENT, <<"<error type=\"unknown\">">>, ?NEWLINE,
357
365
%% Empty output is simply the empty string.
358
366
%% Other output is inside a <system-out> xml tag.
359
367
%% ----------------------------------------------------------------------------
360
 
format_testcase_output([]) -> [];
361
368
format_testcase_output(Output) ->
362
369
    [?INDENT, ?INDENT, <<"<system-out>">>, escape_text(Output), ?NEWLINE, ?INDENT, ?INDENT, <<"</system-out>">>, ?NEWLINE].
363
370
 
375
382
%% Escape a suite's name to generate the filename.
376
383
%% Remark: we might overwrite another testsuite's file.
377
384
%% ----------------------------------------------------------------------------
378
 
escape_suitename([Head | _T] = List) when is_list(Head) ->
379
 
    escape_suitename(lists:flatten(List));
380
385
escape_suitename(Binary) when is_binary(Binary) ->
381
386
    escape_suitename(binary_to_list(Binary));
382
387
escape_suitename("module '" ++ String) ->
384
389
escape_suitename(String) ->
385
390
    escape_suitename(String, []).
386
391
 
387
 
escape_suitename(Binary, Acc) when is_binary(Binary) -> escape_suitename(binary_to_list(Binary), Acc);
388
392
escape_suitename([], Acc) -> lists:reverse(Acc);
389
393
escape_suitename([$  | Tail], Acc) -> escape_suitename(Tail, [$_ | Acc]);
390
394
escape_suitename([$' | Tail], Acc) -> escape_suitename(Tail, Acc);