~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-07 15:07:37 UTC
  • mfrom: (1.2.1 upstream) (5.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090507150737-i4yb5elwinm7r0hc
Tags: 1:13.b-dfsg1-1
* Removed another bunch of non-free RFCs from original tarball
  (closes: #527053).
* Fixed build-dependencies list by adding missing comma. This requires
  libsctp-dev again. Also, added libsctp1 dependency to erlang-base and
  erlang-base-hipe packages because the shared library is loaded via
  dlopen now and cannot be added using dh_slibdeps (closes: #526682).
* Weakened dependency of erlang-webtool on erlang-observer to recommends
  to avoid circular dependencies (closes: #526627).
* Added solaris-i386 to HiPE enabled architectures.
* Made script sources in /usr/lib/erlang/erts-*/bin directory executable,
  which is more convenient if a user wants to create a target Erlang system.
* Shortened extended description line for erlang-dev package to make it
  fit 80x25 terminals.

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_lib.erl 339 2009-04-05 14:10:47Z rcarlsson $
17
17
%%
18
18
%% @copyright 2004-2007 Micka�l R�mond, Richard Carlsson
19
19
%% @author Micka�l R�mond <mickael.remond@process-one.net>
30
30
-include("eunit_internal.hrl").
31
31
 
32
32
 
33
 
-export([dlist_next/1, uniq/1, fun_parent/1, is_string/1, browse_fun/1,
34
 
         command/1, command/2, command/3, trie_new/0, trie_store/2,
35
 
         trie_match/2, split_node/1, consult_file/1, list_dir/1,
36
 
         format_exit_term/1, format_exception/1, format_error/1]).
 
33
-export([dlist_next/1, uniq/1, fun_parent/1, is_string/1, command/1,
 
34
         command/2, command/3, trie_new/0, trie_store/2, trie_match/2,
 
35
         split_node/1, consult_file/1, list_dir/1, format_exit_term/1,
 
36
         format_exception/1, format_error/1]).
37
37
 
38
38
 
39
39
%% Type definitions for describing exceptions
61
61
    case is_stacktrace(Trace) of
62
62
        true ->
63
63
            io_lib:format("~w:~P\n~s",
64
 
                          [Class, Term, 15, format_stacktrace(Trace)]);
 
64
                          [Class, Term, 20, format_stacktrace(Trace)]);
65
65
        false ->
66
66
            format_term(Term)
67
67
    end;
153
153
    error_msg("application not found", "~w", [A]);
154
154
format_error({file_read_error, {_R, Msg, F}}) ->
155
155
    error_msg("error reading file", "~s: ~s", [Msg, F]);
156
 
format_error({context_error, setup_failed, Exception}) ->
 
156
format_error({setup_failed, Exception}) ->
157
157
    error_msg("context setup failed", "~s",
158
158
              [format_exception(Exception)]);
159
 
format_error({context_error, cleanup_failed, Exception}) ->
 
159
format_error({cleanup_failed, Exception}) ->
160
160
    error_msg("context cleanup failed", "~s",
161
161
              [format_exception(Exception)]);
162
 
format_error({context_error, instantiation_failed, Exception}) ->
 
162
format_error({instantiation_failed, Exception}) ->
163
163
    error_msg("instantiation of subtests failed", "~s",
164
164
              [format_exception(Exception)]).
165
165
 
310
310
%% ---------------------------------------------------------------------
311
311
%% Get the name of the containing function for a fun. (This is encoded
312
312
%% in the name of the generated function that implements the fun.)
313
 
 
314
313
fun_parent(F) ->
 
314
    {module, M} = erlang:fun_info(F, module),
315
315
    {name, N} = erlang:fun_info(F, name),
316
316
    case erlang:fun_info(F, type) of
317
317
        {type, external} ->
318
 
            N;
 
318
            {arity, A} = erlang:fun_info(F, arity),
 
319
            {M, N, A};
319
320
        {type, local} ->
320
 
            S = atom_to_list(N),
321
 
            list_to_atom(string:sub_string(S, 2, string:chr(S, $/) - 1))
 
321
            [$-|S] = atom_to_list(N),
 
322
            C1 = string:chr(S, $/),
 
323
            C2 = string:chr(S, $-),
 
324
            {M, list_to_atom(string:sub_string(S, 1, C1 - 1)),
 
325
             list_to_integer(string:sub_string(S, C1 + 1, C2 - 1))}
322
326
    end.
323
327
 
324
328
-ifdef(TEST).
325
329
fun_parent_test() ->
326
 
    fun_parent_test = fun_parent(fun () -> ok end).
 
330
    {?MODULE,fun_parent_test,0} = fun_parent(fun () -> ok end).
327
331
-endif.
328
332
 
329
 
 
330
333
%% ---------------------------------------------------------------------
331
334
%% Ye olde uniq function
332
335
 
348
351
     ]}.
349
352
-endif.
350
353
 
351
 
 
352
 
%% ---------------------------------------------------------------------
353
 
%% Apply arbitrary unary function F with dummy arguments "until it
354
 
%% works". (F must be side effect free! It will be called repeatedly.)
355
 
%% No exceptions will be thrown unless the function actually crashes for
356
 
%% some other reason than being unable to match the argument.
357
 
 
358
 
%% @spec (F::(any()) -> any()) -> {Value::any(), Result::any()}
359
 
 
360
 
browse_fun(F) ->
361
 
    browse_fun(F, arg_values()).
362
 
 
363
 
browse_fun(F, Next) ->
364
 
    case Next() of
365
 
        [V | Next1] ->
366
 
            case try_apply(F, V) of
367
 
                {ok, Result} ->
368
 
                    {V, Result};
369
 
                {error, function_clause} ->
370
 
                    browse_fun(F, Next1);
371
 
                {error, badarity} ->
372
 
                    erlang:error({badarity, {F, 1}});
373
 
                {error, {Class, Reason, Trace}} ->
374
 
                    erlang:raise(Class, Reason, Trace)
375
 
            end;
376
 
        [] ->
377
 
            %% tried everything - this ought to provoke an error
378
 
            F(undefined)
379
 
    end.
380
 
 
381
 
%% Apply argument to function and report whether it succeeded (and with
382
 
%% what return value), or failed due to bad arity or a simple top-level
383
 
%% function_clause error, or if it crashed in some other way.
384
 
 
385
 
%% @spec (F::(any()) -> any(), V::any()) -> 
386
 
%%     {ok, Result::any()}
387
 
%%   | {error, function_clause | badarity | eunit_test:exception()}
388
 
 
389
 
try_apply(F, Arg) ->
390
 
    case erlang:fun_info(F, arity) of
391
 
        {arity, 1} ->
392
 
            {module, M} = erlang:fun_info(F, module),
393
 
            {name, N} = erlang:fun_info(F, name),
394
 
            try_apply(F, Arg, M, N);
395
 
        _ ->
396
 
            {error, badarity}
397
 
    end.
398
 
 
399
 
try_apply(F, Arg, M, N) ->
400
 
    try F(Arg) of
401
 
        X -> {ok, X}
402
 
    catch
403
 
        error:function_clause ->
404
 
            case erlang:get_stacktrace() of
405
 
                [{M, N, _Args} | _] ->
406
 
                    {error, function_clause};
407
 
                Trace ->
408
 
                    {error, {error, function_clause, Trace}}
409
 
            end;
410
 
          Class:Reason ->
411
 
            {error, {Class, Reason, erlang:get_stacktrace()}}
412
 
    end.
413
 
 
414
 
%% test value producers for function browsing
415
 
 
416
 
arg_values() ->
417
 
    Vs = [undefined, ok, true, false, 0, 1],
418
 
    fun () -> arg_values(Vs) end.
419
 
 
420
 
arg_values([V | Vs]) ->
421
 
    [V | fun () -> arg_values(Vs) end];
422
 
arg_values(_) ->
423
 
    (arg_tuples())().
424
 
 
425
 
arg_tuples() ->
426
 
    fun () -> arg_tuples(0) end.
427
 
 
428
 
arg_tuples(N) when N >= 0, N =< 12 ->
429
 
    [erlang:make_tuple(N, undefined) | fun () -> arg_tuples(N + 1) end];
430
 
arg_tuples(_) ->
431
 
    (arg_lists())().
432
 
 
433
 
arg_lists() ->
434
 
    fun () -> arg_lists(0) end.
435
 
 
436
 
arg_lists(N) when N >= 0, N =< 12 ->
437
 
    [lists:duplicate(N, undefined) | fun () -> arg_lists(N + 1) end];
438
 
arg_lists(_) ->
439
 
    [].
440
 
 
441
 
-ifdef(TEST).
442
 
browse_fun_test_() ->
443
 
    {"browsing funs",
444
 
     [?_assertError({badarity, {_, 1}}, browse_fun(fun () -> ok end)),
445
 
      ?_assertError({badarity, {_, 1}}, browse_fun(fun (_,_) -> ok end)),
446
 
      ?_assertError(function_clause, browse_fun(fun (42) -> ok end)),
447
 
      ?_test({_, 17} = browse_fun(fun (_) -> 17 end)),
448
 
      ?_test({_, 17} = browse_fun(fun (undefined) -> 17 end)),
449
 
      ?_test({_, 17} = browse_fun(fun (ok) -> 17 end)),
450
 
      ?_test({_, 17} = browse_fun(fun (true) -> 17 end)),
451
 
      ?_test({_, 17} = browse_fun(fun ({}) -> 17 end)),
452
 
      ?_test({_, 17} = browse_fun(fun ({_}) -> 17 end)),
453
 
      ?_test({_, 17} = browse_fun(fun ({_,_}) -> 17 end)),
454
 
      ?_test({_, 17} = browse_fun(fun ({_,_,_}) -> 17 end)),
455
 
      ?_test({_, 17} = browse_fun(fun ([]) -> 17 end)),
456
 
      ?_test({_, 17} = browse_fun(fun ([_]) -> 17 end)),
457
 
      ?_test({_, 17} = browse_fun(fun ([_,_]) -> 17 end)),
458
 
      ?_test({_, 17} = browse_fun(fun ([_,_,_]) -> 17 end))
459
 
     ]}.
460
 
-endif.
461
 
 
462
 
 
463
354
%% ---------------------------------------------------------------------
464
355
%% Replacement for os:cmd
465
356
 
 
357
%% TODO: Better cmd support, especially on Windows (not much tested)
 
358
%% TODO: Can we capture stderr separately somehow?
 
359
 
466
360
command(Cmd) ->
467
361
    command(Cmd, "").
468
362
 
470
364
    command(Cmd, Dir, []).
471
365
 
472
366
command(Cmd, Dir, Env) ->
473
 
    CD = if Dir == "" -> [];
 
367
    CD = if Dir =:= "" -> [];
474
368
            true -> [{cd, Dir}]
475
369
         end,
476
 
    SetEnv = if Env == [] -> []; 
 
370
    SetEnv = if Env =:= [] -> []; 
477
371
                true -> [{env, Env}]
478
372
             end,
479
373
    Opt = CD ++ SetEnv ++ [stream, exit_status, use_stdio,
587
481
trie_store([E | Es], T) ->
588
482
    case gb_trees:lookup(E, T) of
589
483
        none ->
590
 
            if Es == [] ->
 
484
            if Es =:= [] ->
591
485
                    gb_trees:insert(E, [], T);
592
486
               true ->
593
487
                    gb_trees:insert(E, trie_store(Es, gb_trees:empty()),
608
502
        none ->
609
503
            no;
610
504
        {value, []} ->
611
 
            if Es == [] -> exact;
 
505
            if Es =:= [] -> exact;
612
506
               true -> prefix
613
507
            end;
614
508
        {value, T1} ->
623
517
 
624
518
trie_test_() ->
625
519
    [{"basic representation",
626
 
      [?_assert(trie_new() == gb_trees:empty()),
 
520
      [?_assert(trie_new() =:= gb_trees:empty()),
627
521
       ?_assert(trie_store([1], trie_new())
628
 
                == gb_trees:insert(1, [], gb_trees:empty())),
 
522
                =:= gb_trees:insert(1, [], gb_trees:empty())),
629
523
       ?_assert(trie_store([1,2], trie_new())
630
 
                == gb_trees:insert(1,
631
 
                                   gb_trees:insert(2, [],
632
 
                                                   gb_trees:empty()),
633
 
                                   gb_trees:empty())),
634
 
       ?_assert([] == trie_store([1], [])),
635
 
       ?_assert([] == trie_store([], gb_trees:empty()))
 
524
                =:= gb_trees:insert(1,
 
525
                                    gb_trees:insert(2, [],
 
526
                                                    gb_trees:empty()),
 
527
                                    gb_trees:empty())),
 
528
       ?_assert([] =:= trie_store([1], [])),
 
529
       ?_assert([] =:= trie_store([], gb_trees:empty()))
636
530
      ]},
637
531
     {"basic storing and matching",
638
532
      [?_test(no = trie_match([], trie_new())),