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

« back to all changes in this revision

Viewing changes to lib/kernel/src/global.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:
1
 
%% ``The contents of this file are subject to the Erlang Public License,
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
2
7
%% Version 1.1, (the "License"); you may not use this file except in
3
8
%% compliance with the License. You should have received a copy of the
4
9
%% Erlang Public License along with this software. If not, it can be
5
 
%% retrieved via the world wide web at http://www.erlang.org/.
6
 
%%
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%% 
7
12
%% Software distributed under the License is distributed on an "AS IS"
8
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
14
%% the License for the specific language governing rights and limitations
10
15
%% under the License.
11
 
%%
12
 
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
13
 
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
14
 
%% AB. All Rights Reserved.''
15
 
%%
16
 
%%     $Id $
 
16
%% 
 
17
%% %CopyrightEnd%
17
18
%%
18
19
-module(global).
19
20
-behaviour(gen_server).
72
73
%% Vsn 3 is enhanced with a tag in the synch messages to distinguish
73
74
%%       different synch sessions from each other, see OTP-2766.
74
75
%% Vsn 4 uses a single, permanent, locker process, but works like vsn 3
75
 
%%       when communicating with vsn 3 nodes. Current version of global does
76
 
%%       not support vsn 3 nodes.
 
76
%%       when communicating with vsn 3 nodes. (-R10B)
77
77
%% Vsn 5 uses an ordered list of self() and HisTheLocker when locking
78
 
%%       nodes in the own partition.
 
78
%%       nodes in the own partition. (R11B-)
 
79
 
 
80
%% Current version of global does not support vsn 4 or earlier.
79
81
 
80
82
-define(vsn, 5).
81
83
 
114
116
%%% (the first position is the key):
115
117
%%%
116
118
%%% global_locks (set): {ResourceId, LockRequesterId, [{Pid,RPid,ref()]}
117
 
%%%   pid() is locking ResourceId, ref() is the monitor ref.
 
119
%%%   Pid is locking ResourceId, ref() is the monitor ref.
118
120
%%%   RPid =/= Pid if there is an extra process calling erlang:monitor().
119
121
%%% global_names (set):  {Name, Pid, Method, RPid, ref()}
120
122
%%%   Registered names. ref() is the monitor ref.
800
802
        false ->
801
803
            resend_pre_connect(Node),
802
804
 
803
 
            %% now() is used as a tag to separate different sycnh sessions
 
805
            %% now() is used as a tag to separate different synch sessions
804
806
            %% from each others. Global could be confused at bursty nodeups
805
807
            %% because it couldn't separate the messages between the different
806
808
            %% synch sessions started by a nodeup.
810
812
            S1#state.the_locker ! {nodeup, Node, MyTag},
811
813
 
812
814
            %% In order to be compatible with unpatched R7 a locker
813
 
            %% process was spawned. Vsn 5 is no longer comptabible with
 
815
            %% process was spawned. Vsn 5 is no longer compatible with
814
816
            %% vsn 3 nodes, so the locker process is no longer needed.
815
817
            %% The permanent locker takes its place.
816
818
            NotAPid = no_longer_a_pid,
977
979
        {value, {Node, MyTag, _Resolver}} ->
978
980
            MyTag = get({sync_tag_my, Node}), % assertion
979
981
            case InitMsg of
980
 
                {locker, HisLocker, HisKnown} -> %% before vsn 5
981
 
                    ?trace({old_init_connect,{histhelocker,HisLocker}}),
982
 
                    HisLocker ! {his_locker_new, S#state.the_locker,
983
 
                                 {HisKnown, S#state.known}};
984
 
                
985
 
                {locker, _NoLongerAPid, HisKnown, HisTheLocker} -> %% vsn 5
 
982
                {locker, _NoLongerAPid, _HisKnown0, HisTheLocker} ->
986
983
                    ?trace({init_connect,{histhelocker,HisTheLocker}}),
 
984
                    HisKnown = [],
987
985
                    S#state.the_locker ! {his_the_locker, HisTheLocker,
988
986
                                          {Vsn,HisKnown}, S#state.known}
989
987
            end;
1366
1364
    ?trace({async_del_name, self(), NameL, Ref}),
1367
1365
    case NameL of
1368
1366
        [{Name, Pid}] ->
1369
 
            del_names(Name, Pid, S),
 
1367
            _ = del_names(Name, Pid, S),
1370
1368
            delete_global_name2(Name, S);
1371
1369
        [] ->
1372
1370
            S
1491
1489
                            S#multi.known =:= [] ->
1492
1490
                                200; % just to get started 
1493
1491
                            true ->
1494
 
                                lists:min([1000 + 100*length(S#multi.known), 
1495
 
                                           3000])
 
1492
                                erlang:min(1000 + 100*length(S#multi.known),
 
1493
                                           3000)
1496
1494
                        end
1497
1495
                end,
1498
1496
            S1 = S#multi{just_synced = false},
1511
1509
 
1512
1510
the_locker_message({his_the_locker, HisTheLocker, HisKnown0, _MyKnown}, S) ->
1513
1511
    ?trace({his_the_locker, HisTheLocker, {node,node(HisTheLocker)}}),
1514
 
    HisVsn = 
1515
 
        case HisKnown0 of
1516
 
            {Vsn0, _} when Vsn0 > 4 ->
1517
 
                Vsn0;
1518
 
            _ when is_list(HisKnown0) ->
1519
 
                4
1520
 
        end,
 
1512
    {HisVsn, _HisKnown} = HisKnown0,
 
1513
    true = HisVsn > 4,
1521
1514
    receive
1522
1515
        {nodeup, Node, MyTag} when node(HisTheLocker) =:= Node ->
1523
1516
            ?trace({the_locker_nodeup, {node,Node},{mytag,MyTag}}),
1618
1611
            Him = random_element(Others2),
1619
1612
            #him{locker = HisTheLocker, vsn = HisVsn,
1620
1613
                 node = Node, my_tag = MyTag} = Him,
1621
 
            HisNode = if
1622
 
                           HisVsn < 5 -> [];
1623
 
                           true -> [Node] % prevents deadlock; optimization
1624
 
                       end,
 
1614
            HisNode = [Node],
1625
1615
            Us = [node() | HisNode],
1626
1616
            LockId = locker_lock_id(HisTheLocker, HisVsn),
1627
1617
            ?trace({select_node, self(), {us, Us}}),
 
1618
            %% HisNode = [Node] prevents deadlock:
1628
1619
            {IsLockSet, S2} = lock_nodes_safely(LockId, HisNode, S1),
1629
1620
            case IsLockSet of
1630
1621
                true -> 
1631
1622
                    Known1 = Us ++ S2#multi.known,
1632
1623
                    ?trace({sending_lock_set, self(), {his,HisTheLocker}}),
1633
1624
                    HisTheLocker ! {lock_set, self(), true, S2#multi.known},
1634
 
                    %% OTP-4902
1635
 
                    S3 = lock_set_loop(S2, Him, MyTag, Known1, LockId),
 
1625
                    S3 = lock_is_set(S2, Him, MyTag, Known1, LockId),
1636
1626
                    loop_the_locker(S3);
1637
1627
                false ->
1638
1628
                    loop_the_locker(S2)
1642
1632
%% Version 5: Both sides use the same requester id. Thereby the nodes
1643
1633
%% common to both sides are locked by both locker processes. This
1644
1634
%% means that the lock is still there when the 'new_nodes' message is
1645
 
%% received even if the other side has deleted the lock. Before R11 it
1646
 
%% could be that the lock had been deleted (by the other side) at the
1647
 
%% time 'new_nodes' was sent.
1648
 
locker_lock_id(Pid, 4) ->
1649
 
    %% if node() > Node then Node locks common nodes with {global, Pid}
1650
 
    {?GLOBAL_RID, Pid};
 
1635
%% received even if the other side has deleted the lock.
1651
1636
locker_lock_id(Pid, Vsn) when Vsn > 4 ->
1652
1637
    {?GLOBAL_RID, lists:sort([self(), Pid])}.
1653
1638
 
1668
1653
                            Known = S#multi.known,
1669
1654
                            case set_lock(LockId, Known -- First, 0) of
1670
1655
                                true ->
1671
 
                                    locker_trace(S, ok, {First, Known}),
 
1656
                                    _ = locker_trace(S, ok, {First, Known}),
1672
1657
                                    {true, S};
1673
1658
                                false ->
1674
 
                                    %% Since the boss is locked we should have
1675
 
                                    %% gotten the lock, at least if there are
1676
 
                                    %% no version 4 nodes in the partition or
1677
 
                                    %% someone else is locking 'global'. 
1678
 
                                    %% Calling set_lock with Retries > 0 does
1679
 
                                    %% not seem to speed things up.
 
1659
                                    %% Since the boss is locked we
 
1660
                                    %% should have gotten the lock, at
 
1661
                                    %% least if no one else is locking
 
1662
                                    %% 'global'. Calling set_lock with
 
1663
                                    %% Retries > 0 does not seem to
 
1664
                                    %% speed things up.
1680
1665
                                    SoFar = First ++ Second,
1681
1666
                                    del_lock(LockId, SoFar),
1682
 
                                    locker_trace(S, not_ok, {Known,SoFar}),
 
1667
                                    _ = locker_trace(S, not_ok, {Known,SoFar}),
1683
1668
                                    {false, S}
1684
1669
                            end;
1685
1670
                        false ->
1686
1671
                            del_lock(LockId, First),
1687
 
                            locker_trace(S, not_ok, {Second, First}),
 
1672
                            _ = locker_trace(S, not_ok, {Second, First}),
1688
1673
                            {false, S}
1689
1674
                    end;
1690
1675
                false ->
1691
 
                    locker_trace(S0, not_ok, {First, []}),
 
1676
                    _ = locker_trace(S0, not_ok, {First, []}),
1692
1677
                    {false, S0}
1693
1678
            end;
1694
1679
        false ->
1736
1721
exclude_known(Others, Known) ->
1737
1722
    [N || N <- Others, not lists:member(N#him.node, Known)].
1738
1723
 
1739
 
lock_set_loop(S, Him, MyTag, Known1, LockId) ->
 
1724
lock_is_set(S, Him, MyTag, Known1, LockId) ->
1740
1725
    Node = Him#him.node,
1741
 
    Timeout = if
1742
 
                  Him#him.vsn < 5 -> 5000;
1743
 
                  true -> infinity
1744
 
              end,
1745
1726
    receive
1746
1727
        {lock_set, P, true, _} when node(P) =:= Node ->
1747
1728
            gen_server:cast(global_name_server, 
1762
1743
                    remote = lists:delete(Him, S#multi.remote)};
1763
1744
        {lock_set, P, false, _} when node(P) =:= Node ->
1764
1745
            ?trace({not_both_set, {node,Node},{p, P},{known1,Known1}}),
1765
 
            locker_trace(S, rejected, Known1),
 
1746
            _ = locker_trace(S, rejected, Known1),
1766
1747
            delete_global_lock(LockId, Known1),
1767
1748
            S;
1768
1749
        {cancel, Node, _, Fun} ->
1769
1750
            ?trace({the_locker, cancel2, {node,Node}}),
1770
1751
            call_fun(Fun),
1771
 
            locker_trace(S, rejected, Known1),
 
1752
            _ = locker_trace(S, rejected, Known1),
1772
1753
            delete_global_lock(LockId, Known1),
1773
1754
            remove_node(Node, S);
1774
1755
        {'EXIT', _, _} ->
1775
1756
            ?trace({the_locker, exit, {node,Node}}),
1776
 
            locker_trace(S, rejected, Known1),
 
1757
            _ = locker_trace(S, rejected, Known1),
1777
1758
            delete_global_lock(LockId, Known1),
1778
1759
            S
1779
 
    after
1780
 
        %% OTP-4902
1781
 
        %% A cyclic deadlock could occur in rare cases where three or
1782
 
        %% more nodes waited for a reply from each other.
1783
 
        %% Therefore, reject lock_set attempts in this state from
1784
 
        %% nodes < this node (its enough if at least one node in
1785
 
        %% the cycle rejects and thus breaks the deadlock)
1786
 
        %%
 
1760
        %% There used to be an 'after' clause (OTP-4902), but it is 
 
1761
        %% no longer needed:
1787
1762
        %% OTP-5770. Version 5 of the protocol. Deadlock can no longer
1788
1763
        %% occur due to the fact that if a partition is locked, one
1789
1764
        %% node in the other partition is also locked with the same
1790
1765
        %% lock-id, which makes it impossible for any node in the
1791
1766
        %% other partition to lock its partition unless it negotiates
1792
 
        %% with the first partition. The OTP-4902 code can be removed
1793
 
        %% when there is no need to support nodes running R10B.
1794
 
        Timeout -> 
1795
 
            reject_lock_set(),
1796
 
            lock_set_loop(S, Him, MyTag, Known1, LockId)
1797
 
    end.
1798
 
 
1799
 
reject_lock_set() ->
1800
 
    receive
1801
 
        {lock_set, P, true, _} when node(P) < node() ->
1802
 
            P ! {lock_set, self(), false, []},
1803
 
            reject_lock_set()
1804
 
    after
1805
 
        0 ->
1806
 
            true
 
1767
        %% with the first partition.
1807
1768
    end.
1808
1769
 
1809
1770
%% The locker does the {new_nodes, ...} call before removing the lock.