~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/mnesia/src/mnesia_lib.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-06-11 12:18:07 UTC
  • mfrom: (1.2.2 upstream)
  • Revision ID: james.westby@ubuntu.com-20090611121807-ks7eb4xrt7dsysgx
Tags: 1:13.b.1-dfsg-1
* New upstream release.
* Removed unnecessary dependency of erlang-os-mon on erlang-observer and
  erlang-tools and added missing dependency of erlang-nox on erlang-os-mon
  (closes: #529512).
* Removed a patch to eunit application because the bug was fixed upstream.

Show diffs side-by-side

added added

removed removed

Lines of Context:
143
143
         uniq/1,
144
144
         unlock_table/1,
145
145
         unset/1,
146
 
         update_counter/2,
 
146
         %% update_counter/2,
147
147
         val/1,
148
148
         vcore/0,
149
149
         vcore/1,
208
208
    
209
209
is_string([H|T]) ->
210
210
    if
211
 
        0 =< H, H < 256, integer(H)  -> is_string(T);
 
211
        0 =< H, H < 256, is_integer(H)  -> is_string(T);
212
212
        true -> false
213
213
    end;
214
214
is_string([]) -> true.
235
235
uniq1(Old, [], Ack) ->
236
236
    [Old| Ack].
237
237
 
238
 
to_list(X) when list(X) -> X;
 
238
to_list(X) when is_list(X) -> X;
239
239
to_list(X) -> atom_to_list(X).
240
240
 
241
241
all_nodes() ->
254
254
    IsRunning = is_running(),
255
255
    {IsRunning == yes, node()}.
256
256
 
257
 
is_running(Node) when atom(Node) ->
 
257
is_running(Node) when is_atom(Node) ->
258
258
    case rpc:call(Node, ?MODULE, is_running, []) of
259
259
        {badrpc, _} -> no;
260
260
        X -> X
479
479
        end,
480
480
    lists:zf(F, Tabs).
481
481
 
482
 
etype(X) when integer(X) -> integer;
 
482
etype(X) when is_integer(X) -> integer;
483
483
etype([]) -> nil;
484
 
etype(X) when list(X) -> list;
485
 
etype(X) when tuple(X) -> tuple;
486
 
etype(X) when atom(X) -> atom;
 
484
etype(X) when is_list(X) -> list;
 
485
etype(X) when is_tuple(X) -> tuple;
 
486
etype(X) when is_atom(X) -> atom;
487
487
etype(_) -> othertype.
488
488
 
489
489
remote_copy_holders(Cs) ->
533
533
    set_counter(Name, 0).
534
534
 
535
535
set_counter(Name, Val) ->
536
 
    ?ets_insert(mnesia_gvar, {Name, Val}).
 
536
    ?ets_insert(mnesia_stats, {Name, Val}).
537
537
 
538
538
incr_counter(Name) ->
539
 
    ?ets_update_counter(mnesia_gvar, Name, 1).
 
539
    ?ets_update_counter(mnesia_stats, Name, 1).
540
540
 
541
541
incr_counter(Name, I) ->
542
 
    ?ets_update_counter(mnesia_gvar, Name, I).
 
542
    ?ets_update_counter(mnesia_stats, Name, I).
543
543
 
544
 
update_counter(Name, Val) ->
545
 
    ?ets_update_counter(mnesia_gvar, Name, Val).
 
544
%% update_counter(Name, Val) ->
 
545
%%     ?ets_update_counter(mnesia_stats, Name, Val).
546
546
 
547
547
read_counter(Name) ->
548
 
    ?ets_lookup_element(mnesia_gvar, Name, 2).
 
548
    ?ets_lookup_element(mnesia_stats, Name, 2).
549
549
 
550
550
cs_to_nodes(Cs) ->
551
551
    Cs#cstruct.disc_only_copies ++
574
574
          end,
575
575
    List = lists:append([Fun(I) || I <- Integers]),
576
576
    case mnesia_monitor:get_env(core_dir) of
577
 
        Dir when list(Dir) ->
 
577
        Dir when is_list(Dir) ->
578
578
            filename:absname(lists:concat(["MnesiaCore.", node()] ++ List), Dir);
579
579
        _ ->
580
580
            filename:absname(lists:concat(["MnesiaCore.", node()] ++ List))
583
583
mkcore(CrashInfo) ->
584
584
%   dbg_out("Making a Mnesia core dump...~p~n", [CrashInfo]),
585
585
    Nodes = [node() |nodes()],
586
 
    TidLocks = (catch ets:tab2list(mnesia_tid_locks)),
 
586
    %%TidLocks = (catch ets:tab2list(mnesia_tid_locks)),
 
587
    HeldLocks = (catch mnesia:system_info(held_locks)),
587
588
    Core = [
588
589
            CrashInfo,
589
590
            {time, {date(), time()}},
603
604
            {processes, catch procs()},
604
605
            {relatives, catch relatives()},
605
606
            {workers, catch workers(mnesia_controller:get_workers(2000))},
606
 
            {locking_procs, catch locking_procs(TidLocks)},
 
607
            {locking_procs, catch locking_procs(HeldLocks)},
607
608
 
608
 
            {held_locks, catch mnesia:system_info(held_locks)},
609
 
            {tid_locks, TidLocks},
 
609
            {held_locks, HeldLocks},
610
610
            {lock_queue, catch mnesia:system_info(lock_queue)},
611
611
            {load_info, catch mnesia_controller:get_info(2000)},
612
612
            {trans_info, catch mnesia_tm:get_info(2000)},
680
680
    Linfo = lists:zf(Info, Loaders),
681
681
    [{senders, SInfo},{loader, Linfo}|lists:zf(Info, [{dumper, Dumper}])].
682
682
 
683
 
locking_procs(LockList) when list(LockList) ->
684
 
    Tids = [element(1, Lock) || Lock <- LockList],
 
683
locking_procs(LockList) when is_list(LockList) ->
 
684
    Tids = [element(3, Lock) || Lock <- LockList],
685
685
    UT = uniq(Tids),    
686
686
    Info = fun(Tid) ->
687
687
                   Pid = Tid#tid.pid,
743
743
            Error
744
744
    end.
745
745
 
746
 
vcore(Bin) when binary(Bin) ->
 
746
vcore(Bin) when is_binary(Bin) ->
747
747
    Core = binary_to_term(Bin),
748
748
    Fun = fun({Item, Info}) ->
749
749
                  show("***** ~p *****~n", [Item]),
800
800
    case X of
801
801
        {aborted, Reason} -> Reason;
802
802
        {abort, Reason} -> Reason;
803
 
        Y when atom(Y) -> Y;
804
 
        {'EXIT', {_Reason, {Mod, _, _}}} when atom(Mod) ->
 
803
        Y when is_atom(Y) -> Y;
 
804
        {'EXIT', {_Reason, {Mod, _, _}}} when is_atom(Mod) ->
805
805
            save(X),
806
806
            case atom_to_list(Mod) of
807
807
                [$m, $n, $e|_] -> badarg;
843
843
    error_desc(Reason);
844
844
error_desc({aborted, Reason}) ->
845
845
    error_desc(Reason);
846
 
error_desc(Reason) when tuple(Reason), size(Reason) > 0 ->
 
846
error_desc(Reason) when is_tuple(Reason), size(Reason) > 0 ->
847
847
    setelement(1, Reason, error_desc(element(1, Reason)));
848
848
error_desc(Reason) ->
849
849
    Reason.