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

« back to all changes in this revision

Viewing changes to lib/hipe/util/hipe_pure_ufind.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:
1
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2
 
%%
3
 
%%                     NONDESTRUCTIVE UNION-FIND
4
 
%%
5
 
%% Union-find with path compression; requires a fixed number of
6
 
%% equivalence classes to be merged. This implementation will create
7
 
%% new versions of the datastructures.
8
 
%%
9
 
%%  init(N): initializes N equivalence classes with self as value
10
 
%%     (i.e., class N has value N)
11
 
%%  list(U): list the {Index,EquivClass} pairs of U
12
 
%%  union(X,Y,U): merge equivalence classes X and Y (must be integers!)
13
 
%%  find(X,U): returns {Value,NewU}
14
 
%%  only_find(X,U): returns Index (no path compression is done)
15
 
 
16
 
-module(hipe_pure_ufind).
17
 
-export([init/1,
18
 
         list/1,
19
 
         union/3,
20
 
         find/2,
21
 
         only_find/2]).
22
 
 
23
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
24
 
 
25
 
init(N) ->
26
 
    list_to_tuple(mklist(1,N)).
27
 
 
28
 
mklist(M,N) when M > N -> [];
29
 
mklist(M,N) -> [M|mklist(M+1,N)].
30
 
 
31
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
32
 
 
33
 
list(U) ->
34
 
    list_all(1,size(U),U).
35
 
 
36
 
list_all(M,N,_U) when M > N ->
37
 
    [];
38
 
list_all(M,N,U) -> 
39
 
    {V,NewU} = find(M,U),
40
 
    [{M,V}|list_all(M+1,N,NewU)].
41
 
 
42
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
43
 
%%
44
 
%% Equivalence classes are represented as a vector of integers.
45
 
%% Initially, each position i has the value i, but as classes are
46
 
%% merged, i will get value j, j value k, etc.
47
 
%%   Find traces such a chain until it finds an index i with value i;
48
 
%% this is the true value.
49
 
%%   Union merges two classes by dereferencing both, then
50
 
%% setting one to point to the other.
51
 
%%
52
 
%% Note: there must _never_ be nontrivial circular chains x -> y -> ... -> x
53
 
%%  or the algorithm will loop!
54
 
%%   This is the reason for doing 'find' on both elements in union.
55
 
%%  A second method is given as union2/3, which is slightly more complex
56
 
%%  but sometimes avoids an extra find-operation.
57
 
%%
58
 
%% I haven't measured which one is the fastest in practice.
59
 
 
60
 
%% FIND:
61
 
%% - dereference chain of indices until a self-pointer occurs.
62
 
 
63
 
find(X,U) ->
64
 
    case element(X,U) of
65
 
        X ->  % returned self: chain ended
66
 
            {X,U};
67
 
        Y ->  % returned other: follow chain
68
 
            {V,NewU} = find(Y,U),
69
 
            {V,setelement(X,NewU,V)}
70
 
    end.
71
 
 
72
 
only_find(X,U) ->
73
 
    case element(X,U) of
74
 
        X -> % returned self: end of chain
75
 
            X;
76
 
        Y ->
77
 
            only_find(Y,U)
78
 
    end.
79
 
 
80
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
81
 
%
82
 
% Two implementations of the UNION operation.
83
 
 
84
 
union(X,Y,U) ->
85
 
    union2(X,Y,U).
86
 
 
87
 
% IMPLEMENTATION 1
88
 
%
89
 
% Idea:
90
 
% - Always dereference both arguments. The 'end-points' equivalence
91
 
%   classes can then be joined arbitrarily. (Either can point to the other.)
92
 
%
93
 
% COMMENTED OUT: Currently unused
94
 
 
95
 
% union1(X,Y,U) ->
96
 
%     {V,NxtU} = find(X,U),
97
 
%     {W,NewU} = find(Y,NxtU),
98
 
%     setelement(V,NewU,W).
99
 
 
100
 
% IMPLEMENTATION 2
101
 
%
102
 
% Idea:
103
 
% - Always set a larger index to point to a smaller one. This avoids
104
 
%   nontrivial circular chains and sometimes requires only one find.
105
 
106
 
% Method:
107
 
% - first deref X to V. If V is larger than Y, it can safely point to Y
108
 
%   (since Y won't point to anything as large as V)
109
 
% - otherwise, deref Y to W and set the larger of V or W to point to the
110
 
%   smaller.
111
 
 
112
 
union2(X,Y,U) ->
113
 
    {V,NxtU} = find(X,U),
114
 
    if V > Y ->
115
 
            setelement(V,NxtU,Y);
116
 
       V < Y ->
117
 
            {W,NewU} = find(Y,NxtU),
118
 
            if V < W ->
119
 
                    setelement(W,NewU,V);
120
 
               V > W ->
121
 
                    setelement(V, NewU,W);
122
 
               V == W ->
123
 
                    NewU    % V == W
124
 
            end;
125
 
       true ->
126
 
            NxtU    % V == Y
127
 
    end.