~ubuntu-branches/ubuntu/karmic/erlang/karmic

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

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$ 
 
16
%% $Id: eunit_data.erl 339 2009-04-05 14:10:47Z rcarlsson $ 
17
17
%%
18
18
%% @author Richard Carlsson <richardc@it.uu.se>
19
19
%% @copyright 2006 Richard Carlsson
28
28
 
29
29
-include_lib("kernel/include/file.hrl").
30
30
 
31
 
-export([list/1, iter_init/2, iter_next/2, iter_prev/2, iter_id/1, 
32
 
         list_size/1, enter_context/3]).
 
31
-export([iter_init/2, iter_next/1, iter_prev/1, iter_id/1,
 
32
         enter_context/3, get_module_tests/1]).
33
33
 
34
34
-import(lists, [foldr/3]).
35
35
 
97
97
%%
98
98
%% @type moduleName() = atom()
99
99
%% @type functionName() = atom()
 
100
%% @type arity() = integer()
100
101
%% @type appName() = atom()
101
102
%% @type fileName() = string()
102
103
 
 
104
%% TODO: Can we mark up tests as known-failures?
 
105
%% TODO: Is it possible to handle known timout/setup failures?
 
106
%% TODO: Add diagnostic tests which never fail, but may cause warnings?
 
107
 
103
108
%% ---------------------------------------------------------------------
104
109
%% Abstract test set iterator
105
110
 
121
126
iter_id(#iter{pos = N, parent = Ns}) ->
122
127
    lists:reverse(Ns, [N]).
123
128
 
124
 
%% @spec (testIterator(), Handler) -> none | {testItem(), testIterator()}
125
 
%%    Handler = (term()) -> term()
126
 
 
127
 
iter_next(I, H) ->
128
 
    iter_do(fun iter_next/1, I, H).
129
 
 
130
 
iter_do(F, I, H) ->
131
 
    try F(I)
132
 
    catch
133
 
        throw:R -> H(R)
134
 
    end.
 
129
%% @spec (testIterator()) -> none | {testItem(), testIterator()}
135
130
 
136
131
iter_next(I = #iter{next = []}) ->
137
132
    case next(I#iter.tests) of
147
142
               prev = [T | I#iter.prev],
148
143
               pos = I#iter.pos + 1}}.
149
144
 
150
 
%% @spec (testIterator(), Handler) -> none | {testItem(), testIterator()}
151
 
%%    Handler = (term()) -> term()
152
 
 
153
 
iter_prev(I, H) ->
154
 
    iter_do(fun iter_prev/1, I, H).
 
145
%% @spec (testIterator()) -> none | {testItem(), testIterator()}
155
146
 
156
147
iter_prev(#iter{prev = []}) ->
157
148
    none;
382
373
    case As of
383
374
        [A | As1] ->
384
375
            check_arity(A, 1, T),
385
 
            {data, [fun () -> A(X) end, {with, X, As1}]};
 
376
            {data, [{eunit_lib:fun_parent(A), fun () -> A(X) end},
 
377
                    {with, X, As1}]};
386
378
        [] ->
387
379
            {data, []}
388
380
    end;
389
381
parse({S, T1} = T) when is_list(S) ->
390
382
    case eunit_lib:is_string(S) of
391
383
        true ->
392
 
            group(#group{tests = T1, desc = S});
 
384
            group(#group{tests = T1, desc = list_to_binary(S)});
393
385
        false ->
394
386
            bad_test(T)
395
387
    end;
 
388
parse({S, T1}) when is_binary(S) ->
 
389
    group(#group{tests = T1, desc = S});
396
390
parse(T) when is_tuple(T), size(T) > 2, is_list(element(1, T)) ->
397
391
    [S | Es] = tuple_to_list(T),
398
392
    parse({S, list_to_tuple(Es)});
 
393
parse(T) when is_tuple(T), size(T) > 2, is_binary(element(1, T)) ->
 
394
    [S | Es] = tuple_to_list(T),
 
395
    parse({S, list_to_tuple(Es)});
399
396
parse(M) when is_atom(M) ->
400
397
    parse({module, M});
401
398
parse(T) when is_list(T) ->
417
414
 
418
415
parse_simple({L, F}) when is_integer(L), L >= 0 ->
419
416
    (parse_simple(F))#test{line = L};
 
417
parse_simple({{M,N,A}=Loc, F}) when is_atom(M), is_atom(N), is_integer(A) ->
 
418
    (parse_simple(F))#test{location = Loc};
420
419
parse_simple(F) ->
421
420
    parse_function(F).
422
421
 
423
422
parse_function(F) when is_function(F) ->
424
423
    check_arity(F, 0, F),
425
 
    {module, M} = erlang:fun_info(F, module),
426
 
    #test{f = F, module = M, name = eunit_lib:fun_parent(F)};
 
424
    #test{f = F, location = eunit_lib:fun_parent(F)};
427
425
parse_function({M,F}) when is_atom(M), is_atom(F) ->
428
 
    #test{f = eunit_test:function_wrapper(M, F), module = M, name = F};
 
426
    #test{f = eunit_test:function_wrapper(M, F), location = {M, F, 0}};
429
427
parse_function(F) ->
430
428
    bad_test(F).
431
429
 
546
544
%% @throws {module_not_found, moduleName()}
547
545
 
548
546
get_module_tests(M) ->
549
 
    TestSuffix = ?DEFAULT_TEST_SUFFIX,
550
 
    GeneratorSuffix = ?DEFAULT_GENERATOR_SUFFIX,
551
547
    try M:module_info(exports) of
552
548
        Es ->
553
 
            Fs = testfuns(Es, M, TestSuffix, GeneratorSuffix),
554
 
            Name = atom_to_list(M),
555
 
            case lists:suffix(?DEFAULT_TESTMODULE_SUFFIX, Name) of
556
 
                false ->
557
 
                    Name1 = Name ++ ?DEFAULT_TESTMODULE_SUFFIX,
558
 
                    M1 = list_to_atom(Name1),
559
 
                    try get_module_tests(M1) of
560
 
                        Fs1 ->
561
 
                            Fs ++ [{"module '" ++ Name1 ++ "'", Fs1}]
562
 
                    catch
563
 
                        {module_not_found, M1} ->
564
 
                            Fs
565
 
                    end;
566
 
                true ->
567
 
                    Fs
 
549
            Fs = get_module_tests_1(M, Es),
 
550
            W = ?DEFAULT_MODULE_WRAPPER_NAME,
 
551
            case lists:member({W,1}, Es) of
 
552
                false -> Fs;
 
553
                true -> {generator, fun () -> M:W(Fs) end}
568
554
            end
569
555
    catch
570
556
        error:undef -> 
571
557
            throw({module_not_found, M})
572
558
    end.
573
559
 
 
560
get_module_tests_1(M, Es) ->
 
561
    Fs = testfuns(Es, M, ?DEFAULT_TEST_SUFFIX,
 
562
                  ?DEFAULT_GENERATOR_SUFFIX),
 
563
    Name = atom_to_list(M),
 
564
    case lists:suffix(?DEFAULT_TESTMODULE_SUFFIX, Name) of
 
565
        false ->
 
566
            Name1 = Name ++ ?DEFAULT_TESTMODULE_SUFFIX,
 
567
            M1 = list_to_atom(Name1),
 
568
            try get_module_tests(M1) of
 
569
                Fs1 ->
 
570
                    Fs ++ [{"module '" ++ Name1 ++ "'", Fs1}]
 
571
            catch
 
572
                {module_not_found, M1} ->
 
573
                    Fs
 
574
            end;
 
575
        true ->
 
576
            Fs
 
577
    end.
 
578
 
574
579
testfuns(Es, M, TestSuffix, GeneratorSuffix) ->
575
580
    foldr(fun ({F, 0}, Fs) ->
576
581
                  N = atom_to_list(F),
673
678
    eunit_test:enter_context(S, C, I, F1).
674
679
 
675
680
 
676
 
%% ---------------------------------------------------------------------
677
 
%% Returns a symbolic listing of a set of tests
678
 
%%
679
 
%% @type testInfoList() = [Entry]
680
 
%%   Entry = {item, testId(), Description, testName()}
681
 
%%         | {group, testId(), Description, testInfoList}
682
 
%%   Description = string()
683
 
%% @type testId() = [integer()]
684
 
%% @type testName() = {moduleName(), functionName()}
685
 
%%                  | {moduleName(), functionName(), lineNumber()}
686
 
%% @type lineNumber() = integer().  Proper line numbers are always >= 1.
687
 
%%
688
 
%% @throws {bad_test, term()}
689
 
%%       | {generator_failed, exception()}
690
 
%%       | {no_such_function, eunit_lib:mfa()}
691
 
%%       | {module_not_found, moduleName()}
692
 
%%       | {application_not_found, appName()}
693
 
%%       | {file_read_error, {Reason::atom(), Message::string(),
694
 
%%                            fileName()}}
695
 
%%       | {context_error, instantiation_failed, eunit_lib:exception()}
696
 
 
697
 
list(T) ->
698
 
    list(T, []).
699
 
 
700
 
list(T, ParentID) ->
701
 
    list_loop(iter_init(T, ParentID)).
702
 
 
703
 
list_loop(I) ->
704
 
    case iter_next(I, fun (R) -> throw({error, R}) end) of
705
 
        {T, I1} ->
706
 
            Id = iter_id(I1),
707
 
            case T of
708
 
                #test{} ->
709
 
                    Name = case T#test.line of
710
 
                               0 -> {T#test.module, T#test.name};
711
 
                               Line -> {T#test.module, T#test.name, Line}
712
 
                           end,
713
 
                    [{item, Id, desc_string(T#test.desc), Name}
714
 
                     | list_loop(I1)];
715
 
                #group{context = Context} ->
716
 
                    [{group, Id, desc_string(T#group.desc),
717
 
                      list_context(Context, T#group.tests, Id)}
718
 
                     | list_loop(I1)]
719
 
            end;
720
 
        none ->
721
 
            []
722
 
    end.
723
 
 
724
 
desc_string(undefined) -> "";
725
 
desc_string(S) -> S.
726
 
 
727
 
list_context(undefined, T, ParentId) ->
728
 
    list(T, ParentId);
729
 
list_context(#context{process = local}, T, ParentId) ->
730
 
    browse_context(T, fun (T) -> list(T, ParentId) end);
731
 
list_context(#context{process = spawn}, T, ParentId) ->
732
 
    browse_context(T, fun (T) -> list({spawn, T}, ParentId) end);
733
 
list_context(#context{process = {spawn, N}}, T, ParentId) ->
734
 
    browse_context(T, fun (T) -> list({spawn, N, T}, ParentId) end).
735
 
 
736
 
browse_context(T, F) ->
737
 
    eunit_test:browse_context(T, F).
738
 
 
739
 
list_size({item, _, _, _}) -> 1;
740
 
list_size({group, _, _, Es}) -> list_size(Es);    
741
 
list_size(Es) when is_list(Es) ->
742
 
    lists:foldl(fun (E, N) -> N + list_size(E) end, 0, Es).
743
 
 
744
681
-ifdef(TEST).
745
682
generator_exported_() ->
746
683
    generator().