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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
66
66
-define(match_oid_tid_locks(Tid),   {Tid, '_', '_'}).
67
67
%% mnesia_sticky_locks: contain     {Oid, Node} entries and {Tab, Node} entries (set)
68
68
-define(match_oid_sticky_locks(Oid),{Oid, '_'}).
69
 
%% mnesia_lock_queue: contain       {queue, Oid, Tid, Op, ReplyTo, WaitForTid} entries (ordered_set)
 
69
%% mnesia_lock_queue: contain       {queue, Oid, Tid, Op, ReplyTo, WaitForTid} entries (bag)
70
70
-define(match_oid_lock_queue(Oid),  #queue{oid=Oid, tid='_', op = '_', pid = '_', lucky = '_'}). 
71
71
%% mnesia_lock_counter:             {{write, Tab}, Number} &&
72
72
%%                                  {{read, Tab}, Number} entries  (set)
78
78
    register(?MODULE, self()),
79
79
    process_flag(trap_exit, true),
80
80
    proc_lib:init_ack(Parent, {ok, self()}),
 
81
    case ?catch_val(pid_sort_order) of
 
82
        r9b_plain -> put(pid_sort_order, r9b_plain);
 
83
        standard ->  put(pid_sort_order, standard);
 
84
        _ -> ignore
 
85
    end,
81
86
    loop(#state{supervisor = Parent}).
82
87
 
83
88
val(Var) ->
96
101
l_req_rec(Node, Store) ->
97
102
    ?ets_insert(Store, {nodes, Node}),
98
103
    receive 
99
 
        {?MODULE, Node, {switch, Node2, Req}} ->
100
 
            ?ets_insert(Store, {nodes, Node2}),
101
 
            {?MODULE, Node2} ! Req,
102
 
            {switch, Node2, Req};
103
104
        {?MODULE, Node, Reply} -> 
104
105
            Reply;
105
106
        {mnesia_down, Node} -> 
332
333
    case element(3, Lock) of
333
334
        Tid ->
334
335
            check_lock(Tid, Oid, Locks, TabLocks, X, AlreadyQ, Type);
335
 
        WaitForTid when WaitForTid > Tid -> % Important order
336
 
            check_lock(Tid, Oid, Locks, TabLocks, {queue, WaitForTid}, AlreadyQ, Type);
337
 
        WaitForTid when Tid#tid.pid == WaitForTid#tid.pid ->
338
 
            dbg_out("Spurious lock conflict ~w ~w: ~w -> ~w~n",
339
 
                    [Oid, Lock, Tid, WaitForTid]),  
340
 
%%          check_lock(Tid, Oid, Locks, TabLocks, {queue, WaitForTid}, AlreadyQ);
341
 
            %% BUGBUG Fix this if possible
342
 
            {no, WaitForTid};
343
336
        WaitForTid ->
344
 
            {no, WaitForTid}
 
337
            Queue = allowed_to_be_queued(WaitForTid,Tid),
 
338
            if Queue == true -> 
 
339
                    check_lock(Tid, Oid, Locks, TabLocks, {queue, WaitForTid}, AlreadyQ, Type);
 
340
               Tid#tid.pid == WaitForTid#tid.pid ->
 
341
                    dbg_out("Spurious lock conflict ~w ~w: ~w -> ~w~n",
 
342
                            [Oid, Lock, Tid, WaitForTid]),  
 
343
                    %% Test..
 
344
                    {Tab, _Key} = Oid,
 
345
                    HaveQ = (ets:lookup(mnesia_lock_queue, Oid) /= []) 
 
346
                        orelse (ets:lookup(mnesia_lock_queue,{Tab,?ALL}) /= []),
 
347
                    if 
 
348
                        HaveQ -> 
 
349
                            {no, WaitForTid};
 
350
                        true -> 
 
351
                            check_lock(Tid,Oid,Locks,TabLocks,{queue,WaitForTid},AlreadyQ,Type)
 
352
                    end;
 
353
                    %%{no, WaitForTid};  Safe solution 
 
354
               true ->
 
355
                    {no, WaitForTid}
 
356
            end
345
357
    end;
346
358
 
347
359
check_lock(_, _, [], [], X, {queue, bad_luck}, _) ->
361
373
        true ->
362
374
            %% If there is a queue on that object, read_lock shouldn't be granted
363
375
            ObjLocks = ets:lookup(mnesia_lock_queue, Oid),
364
 
            Greatest = max(ObjLocks),
365
 
            case Greatest of
 
376
            case max(ObjLocks) of
366
377
                empty -> 
367
378
                    check_queue(Tid, Tab, X, AlreadyQ);
368
 
                ObjL when Tid > ObjL -> 
369
 
                    {no, ObjL}; %% Starvation Preemption (write waits for read)
370
379
                ObjL ->
371
 
                    check_queue(Tid, Tab, {queue, ObjL}, AlreadyQ)
 
380
                    case allowed_to_be_queued(ObjL,Tid) of
 
381
                        false ->
 
382
                            %% Starvation Preemption (write waits for read)
 
383
                            {no, ObjL};
 
384
                        true ->
 
385
                            check_queue(Tid, Tab, {queue, ObjL}, AlreadyQ)
 
386
                    end
372
387
            end
373
388
    end;
374
389
 
375
390
check_lock(Tid, Oid, [], TabLocks, X, AlreadyQ, Type) ->
376
391
    check_lock(Tid, Oid, TabLocks, [], X, AlreadyQ, Type).
377
392
 
 
393
%% True if  WaitForTid > Tid -> % Important order
 
394
allowed_to_be_queued(WaitForTid, Tid) ->
 
395
    case get(pid_sort_order) of
 
396
        r9b_plain -> 
 
397
            cmp_tid(true, WaitForTid, Tid) == 1;
 
398
        standard  -> 
 
399
            cmp_tid(false, WaitForTid, Tid) == 1;
 
400
        _ -> 
 
401
            WaitForTid > Tid
 
402
    end.            
 
403
            
378
404
%% Check queue for conflicting locks
379
405
%% Assume that all queued locks belongs to other tid's
380
406
 
386
412
            X;
387
413
        Tid ->
388
414
            X; 
389
 
        WaitForTid when WaitForTid#queue.tid > Tid -> % Important order
390
 
            {queue, WaitForTid};
391
415
        WaitForTid -> 
392
 
            case AlreadyQ of
393
 
                {no, bad_luck} -> {no, WaitForTid};
 
416
            case allowed_to_be_queued(WaitForTid,Tid) of
 
417
                true ->
 
418
                    {queue, WaitForTid};
 
419
                false when AlreadyQ == {no, bad_luck} -> 
 
420
                    {no, WaitForTid};
394
421
                _ ->  
395
422
                    erlang:fault({mnesia_locker, assert, AlreadyQ})
396
423
            end
397
424
    end.
398
425
 
 
426
sort_queue(QL) ->
 
427
    case get(pid_sort_order) of
 
428
        r9b_plain -> 
 
429
            lists:sort(fun(#queue{tid=X},#queue{tid=Y}) -> 
 
430
                               cmp_tid(true, X, Y) == 1
 
431
                       end, QL);
 
432
        standard  -> 
 
433
            lists:sort(fun(#queue{tid=X},#queue{tid=Y}) ->
 
434
                               cmp_tid(false, X, Y) == 1
 
435
                       end, QL);
 
436
        _ -> 
 
437
            lists:reverse(lists:keysort(#queue.tid, QL))
 
438
    end.
 
439
 
399
440
max([]) ->
400
441
    empty;
401
 
max([H|R]) ->
402
 
    max(R, H#queue.tid).
403
 
 
404
 
max([H|R], Tid) when H#queue.tid > Tid ->
405
 
    max(R, H#queue.tid);
406
 
max([_|R], Tid) ->
407
 
    max(R, Tid);
408
 
max([], Tid) ->
409
 
    Tid.
 
442
max(L) ->
 
443
    [#queue{tid=Max}|_] = sort_queue(L),
 
444
    Max.
410
445
 
411
446
%% We can't queue the ixlock requests since it
412
447
%% becomes to complivated for little me :-)
483
518
    ok.
484
519
 
485
520
release_lock({Tid, Oid, {queued, _}}) ->
486
 
    ?ets_match_delete(mnesia_lock_queue, 
487
 
                      #queue{oid=Oid, tid = Tid, op = '_',
488
 
                             pid = '_', lucky = '_'});
 
521
    ?ets_match_delete(mnesia_lock_queue, #queue{oid=Oid, tid = Tid, op = '_',
 
522
                                                pid = '_', lucky = '_'});
 
523
%% case     ?ets_match_object(mnesia_lock_queue, #queue{oid=Oid, tid = Tid, op = '_',
 
524
%%                                                          pid = '_', lucky = '_'}) of
 
525
 
 
526
%%      [] ->  ok;
 
527
%%      Objs -> 
 
528
%%          lists:foreach(fun(Q=#queue{pid=Pid,op=Op,oid=Oid,lucky=L}) -> 
 
529
%%                                ets:delete_object(mnesia_lock_queue,Q),
 
530
%%                                Reply = {not_granted,
 
531
%%                                         #cyclic{op=Op,lock=Op,oid=Oid,lucky=Lucky}},
 
532
%%                                Pid ! {?MODULE,node(),Reply}
 
533
%%                        end, Objs)
 
534
%%     end;
489
535
release_lock({Tid, Oid, Op}) ->
490
536
    if
491
537
        Op == write ->
504
550
                [] -> 
505
551
                    ok;
506
552
                _ ->
507
 
                    Sorted = lists:reverse(lists:keysort(#queue.tid, Queue)),
 
553
                    Sorted = sort_queue(Queue),
508
554
                    try_waiters_obj(Sorted)
509
555
            end;        
510
556
        true -> 
511
557
            Pat = ?match_oid_lock_queue({Tab, '_'}),
512
558
            Queue = ?ets_match_object(mnesia_lock_queue, Pat),      
513
 
            Sorted = lists:reverse(lists:keysort(#queue.tid, Queue)),
 
559
            Sorted = sort_queue(Queue),
514
560
            try_waiters_tab(Sorted)
515
561
    end,
516
562
    ?dbg("RearrQ ~p~n", [Queue]),
618
664
            case need_lock(Store, Tab, Key, Lock)  of
619
665
                yes ->
620
666
                    Ns = w_nodes(Tab),
621
 
                    Res = get_rwlocks_on_nodes(Ns, Ns, Node, Store, Tid, Oid),
 
667
                    Res = get_rwlocks_on_nodes(Ns, rwlock, Node, Store, Tid, Oid),
622
668
                    ?ets_insert(Store, {{locks, Tab, Key}, Lock}),
623
669
                    Res;
624
670
                no ->
633
679
            end
634
680
    end.
635
681
 
636
 
get_rwlocks_on_nodes([Node | Tail], Orig, Node, Store, Tid, Oid) ->
637
 
    Op = {self(), {read_write, Tid, Oid}},
638
 
    {?MODULE, Node} ! Op,
639
 
    ?ets_insert(Store, {nodes, Node}),
640
 
    add_debug(Node),
641
 
    get_rwlocks_on_nodes(Tail, Orig, Node, Store, Tid, Oid);
642
 
get_rwlocks_on_nodes([Node | Tail], Orig, OtherNode, Store, Tid, Oid) ->
643
 
    Op = {self(), {write, Tid, Oid}},
644
 
    {?MODULE, Node} ! Op,
645
 
    add_debug(Node),
646
 
    ?ets_insert(Store, {nodes, Node}),
647
 
    get_rwlocks_on_nodes(Tail, Orig, OtherNode, Store, Tid, Oid);
648
 
get_rwlocks_on_nodes([], Orig, _Node, Store, _Tid, Oid) ->
649
 
    receive_wlocks(Orig, read_write_lock, Store, Oid).
650
 
 
651
682
%% Return a list of nodes or abort transaction
652
683
%% WE also insert any additional where_to_write nodes
653
684
%% in the local store under the key == nodes
735
766
            Nodes;
736
767
        true ->
737
768
            ok
738
 
    end.           
 
769
    end.
739
770
 
740
771
sticky_wlock_table(Tid, Store, Tab) ->
741
772
    sticky_lock(Tid, Store, {Tab, ?ALL}, write).
785
816
            no
786
817
    end.
787
818
 
788
 
add_debug(Node) ->  % Use process dictionary for debug info
789
 
    case get(mnesia_wlock_nodes) of       
790
 
        undefined -> 
791
 
            put(mnesia_wlock_nodes, [Node]);
792
 
        NodeList  ->
793
 
            put(mnesia_wlock_nodes, [Node|NodeList])
794
 
    end.
795
 
 
796
 
del_debug(Node) ->
797
 
    case get(mnesia_wlock_nodes) of
798
 
        undefined ->  % Shouldn't happen
799
 
            ignore;
800
 
        [Node] ->
801
 
            erase(mnesia_wlock_nodes);
802
 
        List -> 
803
 
            put(mnesia_wlock_nodes, lists:delete(Node, List))
804
 
    end.
805
 
 
806
 
%% We first send lock requests to the lockmanagers on all 
 
819
add_debug(Nodes) ->  % Use process dictionary for debug info
 
820
    put(mnesia_wlock_nodes, Nodes).
 
821
 
 
822
del_debug() ->
 
823
    erase(mnesia_wlock_nodes).
 
824
 
 
825
%% We first send lock request to the local node if it is part of the lockers
 
826
%% then the first sorted node then to the rest of the lockmanagers on all 
807
827
%% nodes holding a copy of the table
808
828
 
809
829
get_wlocks_on_nodes([Node | Tail], Orig, Store, Request, Oid) ->
810
830
    {?MODULE, Node} ! Request,
811
831
    ?ets_insert(Store, {nodes, Node}),
812
 
    add_debug(Node),
813
 
    get_wlocks_on_nodes(Tail, Orig, Store, Request, Oid);
814
 
get_wlocks_on_nodes([], Orig, Store, _Request, Oid) ->
815
 
    receive_wlocks(Orig, Orig, Store, Oid).
816
 
 
817
 
receive_wlocks([Node | Tail], Res, Store, Oid) ->
 
832
    receive_wlocks([Node], undefined, Store, Oid),
 
833
    case node() of
 
834
        Node -> %% Local done try one more
 
835
            get_wlocks_on_nodes(Tail, Orig, Store, Request, Oid);
 
836
        _ ->    %% The first succeded cont with the rest  
 
837
            get_wlocks_on_nodes(Tail, Store, Request),
 
838
            receive_wlocks(Tail, Orig, Store, Oid)
 
839
    end;
 
840
get_wlocks_on_nodes([], Orig, _Store, _Request, _Oid) -> 
 
841
    Orig.
 
842
 
 
843
get_wlocks_on_nodes([Node | Tail], Store, Request) ->
 
844
    {?MODULE, Node} ! Request,
 
845
    ?ets_insert(Store,{nodes, Node}),
 
846
    get_wlocks_on_nodes(Tail, Store, Request);
 
847
get_wlocks_on_nodes([], _, _) -> 
 
848
    ok.
 
849
 
 
850
get_rwlocks_on_nodes([ReadNode|Tail], _Res, ReadNode, Store, Tid, Oid) ->
 
851
    Op = {self(), {read_write, Tid, Oid}},
 
852
    {?MODULE, ReadNode} ! Op,
 
853
    ?ets_insert(Store, {nodes, ReadNode}),
 
854
    Res = receive_wlocks([ReadNode], undefined, Store, Oid),
 
855
    case node() of
 
856
        ReadNode -> 
 
857
            get_rwlocks_on_nodes(Tail, Res, ReadNode, Store, Tid, Oid);
 
858
        _ ->
 
859
            get_wlocks_on_nodes(Tail, Store, {self(), {write, Tid, Oid}}),
 
860
            receive_wlocks(Tail, Res, Store, Oid)
 
861
    end;
 
862
get_rwlocks_on_nodes([Node | Tail], Res, ReadNode, Store, Tid, Oid) ->
 
863
    Op = {self(), {write, Tid, Oid}},
 
864
    {?MODULE, Node} ! Op,
 
865
    ?ets_insert(Store, {nodes, Node}),
 
866
    receive_wlocks([Node], undefined, Store, Oid),
 
867
    if node() == Node ->
 
868
            get_rwlocks_on_nodes(Tail, Res, ReadNode, Store, Tid, Oid);
 
869
       Res == rwlock -> %% Hmm      
 
870
            Rest = lists:delete(ReadNode, Tail),
 
871
            Op2 = {self(), {read_write, Tid, Oid}},
 
872
            {?MODULE, ReadNode} ! Op2,
 
873
            ?ets_insert(Store, {nodes, ReadNode}),
 
874
            get_wlocks_on_nodes(Rest, Store, {self(), {write, Tid, Oid}}),
 
875
            receive_wlocks([ReadNode|Rest], undefined, Store, Oid);
 
876
       true ->
 
877
            get_wlocks_on_nodes(Tail, Store, {self(), {write, Tid, Oid}}),
 
878
            receive_wlocks(Tail, Res, Store, Oid)
 
879
    end;
 
880
get_rwlocks_on_nodes([],Res,_,_,_,_) ->
 
881
    Res.
 
882
 
 
883
receive_wlocks([], Res, _Store, _Oid) ->
 
884
    del_debug(),
 
885
    Res;
 
886
receive_wlocks(Nodes = [This|Ns], Res, Store, Oid) ->
 
887
    add_debug(Nodes),
818
888
    receive
819
889
        {?MODULE, Node, granted} ->
820
 
            del_debug(Node),
821
 
            receive_wlocks(Tail, Res, Store, Oid);
 
890
            receive_wlocks(lists:delete(Node,Nodes), Res, Store, Oid);
822
891
        {?MODULE, Node, {granted, Val}} -> %% for rwlocks
823
 
            del_debug(Node),
824
892
            case opt_lookup_in_client(Val, Oid, write) of
825
893
                C when record(C, cyclic) ->
826
 
                    flush_remaining(Tail, Node, {aborted, C});
 
894
                    flush_remaining(Nodes, Node, {aborted, C});
827
895
                Val2 ->
828
 
                    receive_wlocks(Tail, Val2, Store, Oid)
 
896
                    receive_wlocks(lists:delete(Node,Nodes), Val2, Store, Oid)
829
897
            end;
830
898
        {?MODULE, Node, {not_granted, Reason}} ->
831
 
            del_debug(Node),
832
899
            Reason1 = {aborted, Reason},
833
 
            flush_remaining(Tail, Node, Reason1);
 
900
            flush_remaining(Nodes,Node,Reason1);
 
901
        {?MODULE, Node, {switch, Sticky, _Req}} -> %% for rwlocks
 
902
            Tail = lists:delete(Node,Nodes),
 
903
            Nonstuck = lists:delete(Sticky,Tail),
 
904
            [?ets_insert(Store, {nodes, NSNode}) || NSNode <- Nonstuck],
 
905
            case lists:member(Sticky,Tail) of           
 
906
                true ->                     
 
907
                    sticky_flush(Nonstuck,Store),
 
908
                    receive_wlocks([Sticky], Res, Store, Oid);
 
909
                false ->
 
910
                    sticky_flush(Nonstuck,Store),
 
911
                    Res
 
912
            end;
 
913
        {mnesia_down, This} ->  % Only look for down from Nodes in list
 
914
            Reason1 = {aborted, {node_not_running, This}},
 
915
            flush_remaining(Ns, This, Reason1)
 
916
    end.
 
917
 
 
918
sticky_flush([], _) -> 
 
919
    del_debug(),
 
920
    ok;
 
921
sticky_flush(Ns=[Node | Tail], Store) ->
 
922
    add_debug(Ns),
 
923
    receive
 
924
        {?MODULE, Node, _} ->
 
925
            sticky_flush(Tail, Store);
834
926
        {mnesia_down, Node} ->
835
 
            del_debug(Node),
836
 
            Reason1 = {aborted, {node_not_running, Node}},
837
 
            flush_remaining(Tail, Node, Reason1);
838
 
        {?MODULE, Node, {switch, Node2, Req}} -> %% for rwlocks
839
 
            del_debug(Node),
840
 
            add_debug(Node2),
841
 
            ?ets_insert(Store, {nodes, Node2}),
842
 
            {?MODULE, Node2} ! Req,
843
 
            receive_wlocks([Node2 | Tail], Res, Store, Oid)
844
 
    end;
845
 
 
846
 
receive_wlocks([], Res, _Store, _Oid) ->
847
 
    Res.
 
927
            ?ets_delete(Store, {nodes, Node}),
 
928
            sticky_flush(Tail, Store)
 
929
    end.
848
930
 
849
931
flush_remaining([], _SkipNode, Res) ->
 
932
    del_debug(),
850
933
    exit(Res);
851
934
flush_remaining([SkipNode | Tail ], SkipNode, Res) ->
852
 
    del_debug(SkipNode),
853
935
    flush_remaining(Tail, SkipNode, Res);
854
 
flush_remaining([Node | Tail], SkipNode, Res) ->
 
936
flush_remaining(Ns=[Node | Tail], SkipNode, Res) ->
 
937
    add_debug(Ns),
855
938
    receive
856
939
        {?MODULE, Node, _} ->
857
 
            del_debug(Node),
858
940
            flush_remaining(Tail, SkipNode, Res);
859
941
        {mnesia_down, Node} ->
860
 
            del_debug(Node),
861
942
            flush_remaining(Tail, SkipNode, {aborted, {node_not_running, Node}})
862
943
    end.
863
944
 
954
1035
rlock_get_reply(_Node, _Store, _Oid, {not_granted , Reason}) ->
955
1036
    exit({aborted, Reason});
956
1037
 
957
 
rlock_get_reply(_Node, Store, Oid, {switch, N2, Req}) ->
 
1038
rlock_get_reply(_Node, Store, Oid, {switch, N2, Req}) ->    
958
1039
    ?ets_insert(Store, {nodes, N2}),
959
1040
    {?MODULE, N2} ! Req,
960
1041
    rlock_get_reply(N2, Store, Oid, l_req_rec(N2, Store)).
961
1042
 
962
 
 
963
1043
rlock_table(Tid, Store, Tab) ->
964
1044
    rlock(Tid, Store, {Tab, ?ALL}).
965
1045
 
1022
1102
system_code_change(State, _Module, _OldVsn, _Extra) ->
1023
1103
    {ok, State}.
1024
1104
 
 
1105
 
 
1106
%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1107
%% AXD301 patch sort pids according to R9B sort order
 
1108
%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1109
 
 
1110
%% Om R9B == true, g�rs j�mf�relsen som i R9B plain.
 
1111
%% Om R9B == false, g�rs j�mf�relsen som i alla andra releaser.
 
1112
%% cmp_tid(T1, T2) returnerar -1 om T1 < T2, 0 om T1 = T2 och 1 om T1 > T2.
 
1113
 
 
1114
-define(VERSION_MAGIC,       131).
 
1115
-define(ATOM_EXT,            100).
 
1116
-define(PID_EXT,             103).
 
1117
 
 
1118
-record(pid_info, {serial, number, nodename, creation}).
 
1119
 
 
1120
cmp_tid(R9B,
 
1121
        #tid{} = T,
 
1122
        #tid{} = T) when R9B == true; R9B == false ->
 
1123
    0;
 
1124
cmp_tid(R9B,
 
1125
        #tid{counter = C, pid = Pid1},
 
1126
        #tid{counter = C, pid = Pid2}) when R9B == true; R9B == false ->
 
1127
    cmp_pid_info(R9B, pid_to_pid_info(Pid1), pid_to_pid_info(Pid2));
 
1128
cmp_tid(R9B,
 
1129
        #tid{counter = C1},
 
1130
        #tid{counter = C2}) when R9B == true; R9B == false ->
 
1131
    cmp(C1, C2).
 
1132
 
 
1133
cmp_pid_info(_, #pid_info{} = PI, #pid_info{} = PI) ->
 
1134
    0;
 
1135
cmp_pid_info(false,
 
1136
             #pid_info{serial = S, number = N, nodename = NN, creation = C1},
 
1137
             #pid_info{serial = S, number = N, nodename = NN, creation = C2}) ->
 
1138
    cmp(C1, C2);
 
1139
cmp_pid_info(false,
 
1140
             #pid_info{serial = S, number = N, nodename = NN1},
 
1141
             #pid_info{serial = S, number = N, nodename = NN2}) ->
 
1142
    cmp(NN1, NN2);
 
1143
cmp_pid_info(false,
 
1144
             #pid_info{serial = S, number = N1},
 
1145
             #pid_info{serial = S, number = N2}) ->
 
1146
    cmp(N1, N2);
 
1147
cmp_pid_info(false, #pid_info{serial = S1}, #pid_info{serial = S2}) ->
 
1148
    cmp(S1, S2);
 
1149
cmp_pid_info(true,
 
1150
             #pid_info{nodename = NN, creation = C, serial = S, number = N1},
 
1151
             #pid_info{nodename = NN, creation = C, serial = S, number = N2}) ->
 
1152
    cmp(N1, N2);
 
1153
cmp_pid_info(true,
 
1154
             #pid_info{nodename = NN, creation = C, serial = S1},
 
1155
             #pid_info{nodename = NN, creation = C, serial = S2}) ->
 
1156
    cmp(S1, S2);
 
1157
cmp_pid_info(true,
 
1158
             #pid_info{nodename = NN, creation = C1},
 
1159
             #pid_info{nodename = NN, creation = C2}) ->
 
1160
    cmp(C1, C2);
 
1161
cmp_pid_info(true, #pid_info{nodename = NN1}, #pid_info{nodename = NN2}) ->
 
1162
    cmp(NN1, NN2).
 
1163
 
 
1164
cmp(X, X) -> 0;
 
1165
cmp(X1, X2) when X1 < X2 -> -1;
 
1166
cmp(_X1, _X2) -> 1.
 
1167
 
 
1168
pid_to_pid_info(Pid) when pid(Pid) ->
 
1169
    [?VERSION_MAGIC, ?PID_EXT, ?ATOM_EXT, NNL1, NNL0 | Rest]
 
1170
        = binary_to_list(term_to_binary(Pid)),
 
1171
    [N3, N2, N1, N0, S3, S2, S1, S0, Creation] = drop(bytes2int(NNL1, NNL0),
 
1172
                                                      Rest),
 
1173
    #pid_info{serial = bytes2int(S3, S2, S1, S0),
 
1174
              number = bytes2int(N3, N2, N1, N0),
 
1175
              nodename = node(Pid),
 
1176
              creation = Creation}.
 
1177
 
 
1178
drop(0, L) -> L;
 
1179
drop(N, [_|L]) when integer(N), N > 0 -> drop(N-1, L);
 
1180
drop(N, []) when integer(N), N > 0 -> [].
 
1181
 
 
1182
bytes2int(N1, N0) when 0 =< N1, N1 =< 255,
 
1183
                       0 =< N0, N0 =< 255 ->
 
1184
    (N1 bsl 8) bor N0.
 
1185
bytes2int(N3, N2, N1, N0) when 0 =< N3, N3 =< 255,
 
1186
                               0 =< N2, N2 =< 255,
 
1187
                               0 =< N1, N1 =< 255,
 
1188
                               0 =< N0, N0 =< 255 ->
 
1189
    (N3 bsl 24) bor (N2 bsl 16) bor (N1 bsl 8) bor N0.
 
1190