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

« back to all changes in this revision

Viewing changes to lib/hipe/regalloc/hipe_adj_set.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
 
%%% File    : hipe_adj_set.erl
3
 
%%% Author  : Andreas Wallin <d96awa@ida.dis.uu.se>
4
 
%%% Purpose : Used to represent nodes that are connected with edges.
5
 
%%%            This is a much faster way to check if to nodes are
6
 
%%%            connected than checking with the adj_list 
7
 
%%%            data-structure.
8
 
%%% Created : 03 Feb 2000 by Andreas Wallin <d96awa@ida.dis.uu.se>
9
 
%%%----------------------------------------------------------------------
10
 
 
11
 
-module(hipe_adj_set).
12
 
-author("Andreas Wallin").
13
 
-export([new/0, 
14
 
         add_edge/3, 
15
 
         add_edges/3, 
16
 
         remove_edge/3, 
17
 
         remove_edges/3, 
18
 
         adjacent/3]).
19
 
 
20
 
 
21
 
%%%----------------------------------------------------------------------
22
 
% Function:    new
23
 
%
24
 
% Description: Creates a new adj_set data structure. It is used to
25
 
%               represent all edges that are connected in an
26
 
%               undirected graph.
27
 
%
28
 
% Parameters:
29
 
%   None
30
 
%
31
 
% Returns: 
32
 
%   A new adj_set data structure.
33
 
%%%----------------------------------------------------------------------
34
 
new() ->
35
 
    hipe_hash:empty().
36
 
 
37
 
%%%----------------------------------------------------------------------
38
 
% Function:    add_edge
39
 
%
40
 
% Description: Adds a new edge between U and V
41
 
%
42
 
% Parameters:
43
 
%   U              -- A node
44
 
%   V              -- A node
45
 
%   Set            -- An adj_set data-structure
46
 
%
47
 
% Returns: 
48
 
%   An updated adj_set data structure
49
 
%%%----------------------------------------------------------------------
50
 
add_edge(U, U, Set) -> Set;
51
 
add_edge(U, V, Set) ->
52
 
    case adjacent(U, V, Set) of 
53
 
        true  -> Set; % Ok, do nothing. It was already in set
54
 
        false -> Set1 = hipe_hash:insert({U, V}, interfere, Set),
55
 
                 hipe_hash:insert({V, U}, interfere, Set1);
56
 
        _ -> error_logger:error_msg("[~w:add_edge] Could not happen situation",[?MODULE])
57
 
    end.
58
 
 
59
 
%%%----------------------------------------------------------------------
60
 
% Function:    add_edges
61
 
%
62
 
% Description: Adds edges between the node From to a number of other
63
 
%               nodes [T|Ts]
64
 
%
65
 
% Parameters:
66
 
%   From           -- A node that you which to connect to a number of 
67
 
%                      other nodes.
68
 
%   [T|Ts]         -- A list of nodes that you which to connect with 
69
 
%                      the From node
70
 
%   Set            -- An adj_set datastructure
71
 
%
72
 
% Returns: 
73
 
%   An updated adj_set data structure
74
 
%%%----------------------------------------------------------------------
75
 
add_edges(_, [], Set) -> Set;
76
 
add_edges(From, [T|Ts], Set) ->
77
 
    add_edges(From, Ts, add_edge(From, T, Set)).
78
 
 
79
 
%%%----------------------------------------------------------------------
80
 
% Function:    remove_edge
81
 
%
82
 
% Description: Removes the edge between U and V
83
 
%
84
 
% Parameters:
85
 
%   U              -- A node
86
 
%   V              -- A node
87
 
%   Set            -- An adj_set datastructure
88
 
%
89
 
% Returns: 
90
 
%   If the edge exists  --  An updated adj_set data structure
91
 
%   Otherwise           --  Throws an exception
92
 
%%%----------------------------------------------------------------------
93
 
remove_edge(U, U, Set) -> Set;
94
 
remove_edge(U, V, Set) ->
95
 
    case adjacent(U, V, Set) of 
96
 
        true -> Set1 = hipe_hash:delete({U, V}, Set),
97
 
                hipe_hash:delete({V, U}, Set1);
98
 
        false -> throw({adj_set, remove_directed_edge, "Edge does not exist"})
99
 
    end.
100
 
 
101
 
 
102
 
%%%----------------------------------------------------------------------
103
 
% Function:    remove_edges
104
 
%
105
 
% Description: Removes edges between the node From and a number of other
106
 
%               nodes [T|Ts]
107
 
%
108
 
% Parameters:
109
 
%   From           -- A node that you which to remove edges to from
110
 
%   [T|Ts]         -- A list of nodes that you don't want to have an
111
 
%                      edge to the From node any more.
112
 
%   Set            -- An adj_set datastructure
113
 
%
114
 
% Returns: 
115
 
%    If all edges exists  --  An updated adj_set data structure
116
 
%    Otherwise            --  Throws an exception
117
 
%%%----------------------------------------------------------------------
118
 
remove_edges(_, [], Set) -> Set;
119
 
remove_edges(From, [T|Ts], Set) ->
120
 
    remove_edges(From, Ts, remove_edge(From, T, Set)).
121
 
 
122
 
 
123
 
%%%----------------------------------------------------------------------
124
 
% Function:    adjacent
125
 
%
126
 
% Description: Tells if an edge exists between U and V
127
 
%
128
 
% Parameters:
129
 
%   U              -- A node
130
 
%   V              -- A node
131
 
%   Set            -- An adj_set datastructure
132
 
%
133
 
% Returns: 
134
 
%   true   --  If there exists an edge between U and V
135
 
%   false  --  Otherwise
136
 
%%%----------------------------------------------------------------------
137
 
adjacent(U, V, Set) ->
138
 
    case hipe_hash:lookup({U, V}, Set) of 
139
 
        {found, _} -> true;
140
 
        not_found -> false;
141
 
        _ -> exit({adj_set, adjacent, "Could not happend"})
142
 
    end.
143
 
 
144