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

« back to all changes in this revision

Viewing changes to lib/hipe/regalloc/hipe_reg_worklists.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
%%% -*- erlang-indent-level: 2 -*-
 
2
%%% $Id$
1
3
%%%----------------------------------------------------------------------
2
4
%%% File    : hipe_reg_worklists.erl
3
 
%%% Author  : Andreas Wallin <d96awa@ida.dis.uu.se>
 
5
%%% Author  : Andreas Wallin <d96awa@csd.uu.se>
4
6
%%% Purpose : Represents sets of nodes/temporaries that we are
5
7
%%%           working on, such as simplify and spill sets.
6
 
%%% Created : 3 Feb 2000 by Andreas Wallin <d96awa@ida.dis.uu.se>
 
8
%%% Created : 3 Feb 2000 by Andreas Wallin <d96awa@csd.uu.se>
 
9
%%% Modified: Spring 2005 by NilsOla Linnermark <nilsola@abc.se>
 
10
%%%           to suit the optimistic coalesching allocator
7
11
%%%----------------------------------------------------------------------
8
12
 
9
13
-module(hipe_reg_worklists).
10
14
-author(['Andreas Wallin',  'Thorild Sel�n']).
11
 
-export([new/4,
 
15
-export([new/5,                 % only used by optimistic allocator
 
16
         new/6,
12
17
         simplify/1,
13
18
         spill/1,
14
19
         freeze/1,
15
 
         add/3, 
16
 
         remove/3,
17
 
         is_empty/2,
18
 
         member/3,
19
 
         head/2,
20
 
         tail/2,
21
 
         transfer/4
 
20
         stack/1,
 
21
         add_simplify/2,
 
22
         add_freeze/2,
 
23
         add_coalesced/2,
 
24
         add_coalesced/3,       % only used by optimistic allocator
 
25
         add_spill/2,
 
26
         push_stack/3,
 
27
         remove_simplify/2,
 
28
         remove_spill/2,
 
29
         remove_freeze/2,
 
30
         is_empty_simplify/1,
 
31
         is_empty_spill/1,
 
32
         is_empty_freeze/1,
 
33
         member_freeze/2,
 
34
         member_coalesced_to/2, % only used by optimistic allocator
 
35
         member_stack_or_coalesced/2,
 
36
         non_stacked_or_coalesced_nodes/2,
 
37
         transfer_freeze_simplify/2,
 
38
         transfer_freeze_spill/2
22
39
        ]).
 
40
-ifdef(DEBUG_PRINTOUTS).
 
41
-export([print_memberships/1]).
 
42
-endif.
23
43
 
24
44
-record(worklists, 
25
 
        {simplify, % Less that K nodes
26
 
         spill,    % Greater than K modes
27
 
         freeze    % Less than K move related nodes
 
45
        {simplify,   % Low-degree nodes (if coalescing non move-related)
 
46
         stack,      % Stack of removed low-degree nodes, with adjacency lists
 
47
         membership, % Mapping from temp to which set it is in
 
48
         coalesced_to,  % if the node is coalesced to (only used by optimistic allocator)
 
49
         spill,      % Significant-degree nodes
 
50
         freeze      % Low-degree move-related nodes
28
51
        }).
29
52
 
30
 
%%%----------------------------------------------------------------------
31
 
% Function:    new
32
 
%
33
 
% Description: Constructor for worklists structure
34
 
%
35
 
% Parameters:
36
 
%   IG              -- Interference graph
37
 
%   Node_sets       -- Node information
38
 
%   Move_sets       -- Move information
39
 
%   K               -- Number of registers
40
 
%   
41
 
% Returns:
42
 
%   A new worklists data structure
43
 
%
44
 
%%%----------------------------------------------------------------------
45
 
 
46
 
new(IG, Node_sets, Move_sets, K) ->
47
 
    init(hipe_node_sets:initial(Node_sets), K, hipe_ig:degree(IG), Move_sets, empty()).
48
 
         
49
 
% construct an empty initialized worklists data structure
50
 
empty() ->
 
53
%%-ifndef(DEBUG).
 
54
%%-define(DEBUG,true).
 
55
%%-endif.
 
56
-include("../main/hipe.hrl").
 
57
 
 
58
%%%----------------------------------------------------------------------
 
59
%% Function:    new
 
60
%%
 
61
%% Description: Constructor for worklists structure
 
62
%%
 
63
%% Parameters:
 
64
%%   IG              -- Interference graph
 
65
%%   Target          -- Target module name
 
66
%%   CFG             -- Target-specific CFG
 
67
%%   Move_sets       -- Move information
 
68
%%   K               -- Number of registers
 
69
%%   
 
70
%% Returns:
 
71
%%   A new worklists data structure
 
72
%%
 
73
%%%----------------------------------------------------------------------
 
74
 
 
75
new(IG, Target, CFG, K, No_temporaries) -> % only used by optimistic allocator
 
76
  CoalescedTo = hipe_bifs:array(No_temporaries, 'none'),
 
77
  init(initial(Target, CFG), K, IG, empty(No_temporaries, CoalescedTo)).
 
78
 
 
79
new(IG, Target, CFG, Move_sets, K, No_temporaries) ->
 
80
  init(initial(Target, CFG), K, IG, Move_sets, empty(No_temporaries, [])).
 
81
 
 
82
initial(Target, CFG) ->
 
83
  {Min_temporary, Max_temporary} = Target:var_range(CFG),
 
84
  NonAlloc = Target:non_alloc(CFG),
 
85
  non_precoloured(Target, Min_temporary, Max_temporary, [])
 
86
    -- [Target:reg_nr(X) || X <- NonAlloc].
 
87
 
 
88
non_precoloured(Target, Current, Max_temporary, Initial) ->
 
89
  if Current > Max_temporary ->
 
90
      Initial;
 
91
     true ->
 
92
      NewInitial =
 
93
        case Target:is_precoloured(Current) of
 
94
          true -> Initial;
 
95
          false -> [Current|Initial]
 
96
        end,
 
97
      non_precoloured(Target, Current+1, Max_temporary, NewInitial)
 
98
  end.
 
99
 
 
100
%% construct an empty initialized worklists data structure
 
101
empty(No_temporaries, CoalescedTo) ->
51
102
    #worklists{
 
103
       membership = hipe_bifs:array(No_temporaries, 'none'),
 
104
       coalesced_to = CoalescedTo, % only used by optimistic allocator
52
105
       simplify = ordsets:new(),
 
106
       stack    = [],
53
107
       spill    = ordsets:new(),
54
108
       freeze   = ordsets:new()
55
109
      }.    
56
110
 
57
 
% Selectors for worklists record
 
111
%% Selectors for worklists record
58
112
 
59
113
simplify(Worklists) -> Worklists#worklists.simplify.
60
114
spill(Worklists)    -> Worklists#worklists.spill.
61
115
freeze(Worklists)   -> Worklists#worklists.freeze.
62
 
 
63
 
 
64
 
% Updating worklists records
 
116
stack(Worklists)    -> Worklists#worklists.stack.
 
117
 
 
118
%% Updating worklists records
65
119
 
66
120
set_simplify(Simplify, Worklists) ->
67
121
    Worklists#worklists{simplify = Simplify}.
72
126
 
73
127
 
74
128
%%----------------------------------------------------------------------
75
 
% Function:    init
76
 
%
77
 
% Description: Initializes worklists
78
 
%
79
 
% Parameters:
80
 
%   Initials        -- Not precolored temporaries
81
 
%   K               -- Number of registers
82
 
%   Degree          -- Degree information for nodes
83
 
%   Move_sets       -- Move information
84
 
%   Worklists       -- (Empty) worklists structure
85
 
%   
86
 
% Returns:
87
 
%   Initialized worklists structure
88
 
%
 
129
%% Function:    init
 
130
%%
 
131
%% Description: Initializes worklists
 
132
%%
 
133
%% Parameters:
 
134
%%   Initials        -- Not precoloured temporaries
 
135
%%   K               -- Number of registers
 
136
%%   IG              -- Interference graph
 
137
%%   Move_sets       -- Move information
 
138
%%   Worklists       -- (Empty) worklists structure
 
139
%%   
 
140
%% Returns:
 
141
%%   Initialized worklists structure
 
142
%%
89
143
%%----------------------------------------------------------------------
90
144
 
 
145
init([], _, _, Worklists) -> Worklists;
 
146
init([Initial|Initials], K, IG, Worklists) -> 
 
147
    case hipe_ig:is_trivially_colourable(Initial, K, IG) of
 
148
        false ->
 
149
            New_worklists = add_spill(Initial, Worklists),
 
150
            init(Initials, K, IG, New_worklists);
 
151
        _ ->
 
152
            New_worklists = add_simplify(Initial, Worklists),
 
153
            init(Initials, K, IG, New_worklists)
 
154
    end.
 
155
 
91
156
init([], _, _, _, Worklists) -> Worklists;
92
 
init([Initial|Initials], K, Degree, Move_sets, Worklists) -> 
93
 
    case hipe_degree:is_simple(Initial, K, Degree) of
 
157
init([Initial|Initials], K, IG, Move_sets, Worklists) -> 
 
158
    case hipe_ig:is_trivially_colourable(Initial, K, IG) of
94
159
        false ->
95
 
            New_worklists = add(spill, Initial, Worklists),
96
 
            init(Initials, K, Degree, Move_sets, New_worklists);
 
160
            New_worklists = add_spill(Initial, Worklists),
 
161
            init(Initials, K, IG, Move_sets, New_worklists);
97
162
        _ ->
98
163
            case hipe_moves:move_related(Initial, Move_sets) of
99
164
                true ->
100
 
                    New_worklists = add(freeze, Initial, Worklists),
101
 
                    init(Initials, K, Degree, Move_sets, New_worklists);
 
165
                    New_worklists = add_freeze(Initial, Worklists),
 
166
                    init(Initials, K, IG, Move_sets, New_worklists);
102
167
                _ ->
103
 
                    New_worklists = add(simplify, Initial, Worklists),
104
 
                    init(Initials, K, Degree, Move_sets, New_worklists)
 
168
                    New_worklists = add_simplify(Initial, Worklists),
 
169
                    init(Initials, K, IG, Move_sets, New_worklists)
105
170
            end
106
171
    end.
107
172
 
108
 
 
109
 
%%%----------------------------------------------------------------------
110
 
% Function:    is_empty
111
 
%
112
 
% Description: Tests if the selected worklist if empty or not.
113
 
%
114
 
% Parameters:
115
 
%   simplify, spill, freeze  -- The worklist you want to check if it's
116
 
%                                empty
117
 
%   Worklists                -- A worklists data structure
118
 
%   
119
 
% Returns:
120
 
%   true  -- If the worklist was empty
121
 
%   false -- otherwise
122
 
%
123
 
%%%----------------------------------------------------------------------
124
 
is_empty(simplify, Worklists) ->
125
 
    simplify(Worklists) == [];
126
 
is_empty(spill, Worklists) ->
127
 
    spill(Worklists) == [];
128
 
is_empty(freeze, Worklists) ->
129
 
    freeze(Worklists) == [].
130
 
 
131
 
 
132
 
 
133
 
%%%----------------------------------------------------------------------
134
 
% Function:    head
135
 
%
136
 
% Description: Takes out the head (first element) from one of the
137
 
%               worklists.
138
 
%
139
 
% Parameters:
140
 
%   simplify, spill, freeze  -- The worklist you want the first element
141
 
%                                 of
142
 
%   Worklists                -- A worklists data structure
143
 
%   
144
 
% Returns:
145
 
%   First element from selected worklist. The worklists structure is
146
 
%    unchanged.
147
 
%
148
 
%%%----------------------------------------------------------------------
149
 
head(simplify, Worklists) ->
150
 
    [H, _] = simplify(Worklists),
151
 
    H;
152
 
head(spill, Worklists) ->
153
 
    [H, _] = spill(Worklists),
154
 
    H;
155
 
head(freeze, Worklists) ->
156
 
    [H, _] = freeze(Worklists),
157
 
    H.
158
 
 
159
 
 
160
 
%%%----------------------------------------------------------------------
161
 
% Function:    tail
162
 
%
163
 
% Description: Takes out the tail (elements after the first) from one 
164
 
%               of the worklists.
165
 
%
166
 
% Parameters:
167
 
%   simplify, spill, freeze  -- The worklist you want the tail of
168
 
%   Worklists                -- A worklists data structure
169
 
%   
170
 
% Returns:
171
 
%   The tail elements from selected worklist. The worklists structure 
172
 
%    is unchanged.
173
 
%
174
 
%%%----------------------------------------------------------------------
175
 
tail(simplify, Worklists) ->
176
 
    [_, T] = simplify(Worklists),
177
 
    T;
178
 
tail(spill, Worklists) ->
179
 
    [_, T] = spill(Worklists),
180
 
    T;
181
 
tail(freeze, Worklists) ->
182
 
    [_, T] = freeze(Worklists),
183
 
    T.
184
 
 
185
 
 
186
 
%%%----------------------------------------------------------------------
187
 
% Function:    add
188
 
%
189
 
% Description: Adds one element to one of the worklists.
190
 
%
191
 
% Parameters:
192
 
%   simplify, spill, freeze  -- The worklist you want to add the element
193
 
%                                 to
194
 
%   Element                  -- An element you want to add to the 
195
 
%                                selected worklist. The element should 
196
 
%                                be a node/temporary.
197
 
%   Worklists                -- A worklists data structure
198
 
%   
199
 
% Returns:
200
 
%   An worklists data-structure that have Element in selected 
201
 
%    worklist.
202
 
%
203
 
%%%----------------------------------------------------------------------
204
 
add(simplify, Element, Worklists) ->
205
 
    Simplify = ordsets:add_element(Element, simplify(Worklists)),
206
 
    set_simplify(Simplify, Worklists);
207
 
add(spill, Element, Worklists) ->
208
 
    Spill = ordsets:add_element(Element, spill(Worklists)),
209
 
    set_spill(Spill, Worklists);
210
 
add(freeze, Element, Worklists) ->
211
 
    Freeze = ordsets:add_element(Element, freeze(Worklists)),
212
 
    set_freeze(Freeze, Worklists).
213
 
 
214
 
 
215
 
%%%----------------------------------------------------------------------
216
 
% Function:    remove
217
 
%
218
 
% Description: Removes one element to one of the worklists.
219
 
%
220
 
% Parameters:
221
 
%   simplify, spill, freeze  -- The worklist you want to remove the element
222
 
%                                 from.
223
 
%   Element                  -- An element you want to remove from the 
224
 
%                                selected worklist. The element should 
225
 
%                                be a node/temporary.
226
 
%   Worklists                -- A worklists data structure
227
 
%   
228
 
% Returns:
229
 
%   A worklists data-structure that don't have Element in selected 
230
 
%    worklist.
231
 
%
232
 
%%%----------------------------------------------------------------------
233
 
remove(simplify, Element, Worklists) ->
234
 
    Simplify = ordsets:del_element(Element, simplify(Worklists)),
235
 
    set_simplify(Simplify, Worklists);
236
 
remove(spill, Element, Worklists) ->
237
 
    Spill = ordsets:del_element(Element, spill(Worklists)),
238
 
    set_spill(Spill, Worklists);
239
 
remove(freeze, Element, Worklists) ->
240
 
    Freeze = ordsets:del_element(Element, freeze(Worklists)),
241
 
    set_freeze(Freeze, Worklists).
242
 
 
243
 
 
244
 
%%%----------------------------------------------------------------------
245
 
% Function:    transfer
246
 
%
247
 
% Description: Moves element from one worklist to another.
248
 
%
249
 
% Parameters:
250
 
%   From           -- One of simplify, spill, freeze.
251
 
%   To             -- One of simplify, spill, freeze.
252
 
%   Element        -- Element you want to move.
253
 
%   Worklists                -- A worklists data structure
254
 
%   
255
 
% Returns:
256
 
%   A worklists data-structure with element moved from the From
257
 
%     worklist to the To worklist.
258
 
%
259
 
%%%----------------------------------------------------------------------
260
 
transfer(From, From, _, Worklists) -> Worklists;
261
 
transfer(From, To, Element, Worklists) ->
262
 
    add(To, Element, remove(From, Element, Worklists)).
263
 
 
264
 
 
265
 
%%%----------------------------------------------------------------------
266
 
% Function:    member
267
 
%
268
 
% Description: Checks if one element if member of selected worklist.
269
 
%
270
 
% Parameters:
271
 
%   simplify, spill, freeze  -- The worklist you want to know if 
272
 
%                                Element is a member of.
273
 
%   Element                  -- Element you want to know if it's a 
274
 
%                                member of selected worklist.
275
 
%   Worklists                -- A worklists data structure
276
 
%   
277
 
% Returns:
278
 
%   true   --  if Element is a member of selected worklist
279
 
%   false  --  Otherwise
280
 
%
281
 
%%%----------------------------------------------------------------------
282
 
member(simplify, Element, Worklists) ->
283
 
    ordsets:is_element(Element, simplify(Worklists));
284
 
member(spill, Element, Worklists) ->
285
 
    ordsets:is_element(Element, spill(Worklists));
286
 
member(freeze, Element, Worklists) ->
287
 
    ordsets:is_element(Element, freeze(Worklists)).
 
173
%%%----------------------------------------------------------------------
 
174
%% Function:    is_empty
 
175
%%
 
176
%% Description: Tests if the selected worklist if empty or not.
 
177
%%
 
178
%% Parameters:
 
179
%%   Worklists                -- A worklists data structure
 
180
%%   
 
181
%% Returns:
 
182
%%   true  -- If the worklist was empty
 
183
%%   false -- otherwise
 
184
%%
 
185
%%%----------------------------------------------------------------------
 
186
 
 
187
is_empty_simplify(Worklists) ->
 
188
  simplify(Worklists) =:= [].
 
189
 
 
190
is_empty_spill(Worklists) ->
 
191
  spill(Worklists) =:= [].
 
192
 
 
193
is_empty_freeze(Worklists) ->
 
194
  freeze(Worklists) =:= [].
 
195
 
 
196
%%%----------------------------------------------------------------------
 
197
%% Function:    add
 
198
%%
 
199
%% Description: Adds one element to one of the worklists.
 
200
%%
 
201
%% Parameters:
 
202
%%   Element                  -- An element you want to add to the 
 
203
%%                                selected worklist. The element should 
 
204
%%                                be a node/temporary.
 
205
%%   Worklists                -- A worklists data structure
 
206
%%   
 
207
%% Returns:
 
208
%%   An worklists data-structure that have Element in selected 
 
209
%%    worklist.
 
210
%%
 
211
%%%----------------------------------------------------------------------
 
212
add_coalesced(Element, Worklists) ->
 
213
  Membership = Worklists#worklists.membership,
 
214
  hipe_bifs:array_update(Membership, Element, 'stack_or_coalesced'),
 
215
  Worklists.
 
216
 
 
217
add_coalesced(From, To, Worklists) -> % only used by optimistic allocator
 
218
  Membership = Worklists#worklists.membership,
 
219
  hipe_bifs:array_update(Membership, From, 'stack_or_coalesced'),
 
220
  Coalesced_to = Worklists#worklists.coalesced_to,
 
221
  hipe_bifs:array_update(Coalesced_to, To, 'coalesced_to'),
 
222
  Worklists.
 
223
 
 
224
add_simplify(Element, Worklists) ->
 
225
  Membership = Worklists#worklists.membership,
 
226
  hipe_bifs:array_update(Membership, Element, 'simplify'),
 
227
  Simplify = ordsets:add_element(Element, simplify(Worklists)),
 
228
  set_simplify(Simplify, Worklists).
 
229
 
 
230
add_spill(Element, Worklists) ->
 
231
  Membership = Worklists#worklists.membership,
 
232
  hipe_bifs:array_update(Membership, Element, 'spill'),
 
233
  Spill = ordsets:add_element(Element, spill(Worklists)),
 
234
  set_spill(Spill, Worklists).
 
235
 
 
236
add_freeze(Element, Worklists) ->
 
237
  Membership = Worklists#worklists.membership,
 
238
  hipe_bifs:array_update(Membership, Element, 'freeze'),
 
239
  Freeze = ordsets:add_element(Element, freeze(Worklists)),
 
240
  set_freeze(Freeze, Worklists).
 
241
 
 
242
push_stack(Node, AdjList, Worklists) ->
 
243
  Membership = Worklists#worklists.membership,
 
244
  hipe_bifs:array_update(Membership, Node, 'stack_or_coalesced'),
 
245
  Stack = Worklists#worklists.stack,
 
246
  Worklists#worklists{stack = [{Node,AdjList}|Stack]}.
 
247
 
 
248
%%%----------------------------------------------------------------------
 
249
%% Function:    remove
 
250
%%
 
251
%% Description: Removes one element to one of the worklists.
 
252
%%
 
253
%% Parameters:
 
254
%%   Element                  -- An element you want to remove from the 
 
255
%%                                selected worklist. The element should 
 
256
%%                                be a node/temporary.
 
257
%%   Worklists                -- A worklists data structure
 
258
%%   
 
259
%% Returns:
 
260
%%   A worklists data-structure that don't have Element in selected 
 
261
%%    worklist.
 
262
%%
 
263
%%%----------------------------------------------------------------------
 
264
remove_simplify(Element, Worklists) ->
 
265
  Membership = Worklists#worklists.membership,
 
266
  hipe_bifs:array_update(Membership, Element, 'none'),
 
267
  Simplify = ordsets:del_element(Element, simplify(Worklists)),
 
268
  set_simplify(Simplify, Worklists).
 
269
 
 
270
remove_spill(Element, Worklists) ->
 
271
  Membership = Worklists#worklists.membership,
 
272
  hipe_bifs:array_update(Membership, Element, 'none'),
 
273
  Spill = ordsets:del_element(Element, spill(Worklists)),
 
274
  set_spill(Spill, Worklists).
 
275
 
 
276
remove_freeze(Element, Worklists) ->
 
277
  Membership = Worklists#worklists.membership,
 
278
  hipe_bifs:array_update(Membership, Element, 'none'),
 
279
  Freeze = ordsets:del_element(Element, freeze(Worklists)),
 
280
  set_freeze(Freeze, Worklists).
 
281
 
 
282
%%%----------------------------------------------------------------------
 
283
%% Function:    transfer
 
284
%%
 
285
%% Description: Moves element from one worklist to another.
 
286
%%
 
287
%%%----------------------------------------------------------------------
 
288
transfer_freeze_simplify(Element, Worklists) ->
 
289
  add_simplify(Element, remove_freeze(Element, Worklists)).
 
290
 
 
291
transfer_freeze_spill(Element, Worklists) ->
 
292
  add_spill(Element, remove_freeze(Element, Worklists)).
 
293
 
 
294
%%%----------------------------------------------------------------------
 
295
%% Function:    member
 
296
%%
 
297
%% Description: Checks if one element if member of selected worklist.
 
298
%%
 
299
%% Parameters:
 
300
%%   Element                  -- Element you want to know if it's a 
 
301
%%                                member of selected worklist.
 
302
%%   Worklists                -- A worklists data structure
 
303
%%   
 
304
%% Returns:
 
305
%%   true   --  if Element is a member of selected worklist
 
306
%%   false  --  Otherwise
 
307
%%
 
308
%%%----------------------------------------------------------------------
 
309
 
 
310
member_coalesced_to(Element, Worklists) -> % only used by optimistic allocator
 
311
    hipe_bifs:array_sub(Worklists#worklists.coalesced_to, Element) =:= 'coalesced_to'.
 
312
 
 
313
member_freeze(Element, Worklists) ->
 
314
  hipe_bifs:array_sub(Worklists#worklists.membership, Element) =:= 'freeze'.
 
315
 
 
316
member_stack_or_coalesced(Element, Worklists) ->
 
317
  hipe_bifs:array_sub(Worklists#worklists.membership, Element) =:= 'stack_or_coalesced'.
 
318
 
 
319
non_stacked_or_coalesced_nodes(Nodes, Worklists) ->
 
320
  Membership = Worklists#worklists.membership,
 
321
  [Node || Node <- Nodes,
 
322
           hipe_bifs:array_sub(Membership, Node) =/= 'stack_or_coalesced'].
 
323
 
 
324
%%%----------------------------------------------------------------------
 
325
%% Print functions - only used for debugging
 
326
 
 
327
-ifdef(DEBUG_PRINTOUTS).
 
328
print_memberships(Worklists) ->
 
329
  ?debug_msg("Worklist memeberships:\n", []),
 
330
  Membership = Worklists#worklists.membership,
 
331
  NrElems = hipe_bifs:array_length(Membership),
 
332
  Coalesced_to = Worklists#worklists.coalesced_to,
 
333
  print_membership(NrElems, Membership, Coalesced_to).
 
334
 
 
335
print_membership(0, _, _) ->
 
336
  true;
 
337
print_membership(Element, Membership, Coalesced_to) ->
 
338
  NextElement = Element - 1,
 
339
  ?debug_msg("worklist ~w ~w ~w\n",
 
340
             [NextElement, hipe_bifs:array_sub(Membership, NextElement),
 
341
                           hipe_bifs:array_sub(Coalesced_to, NextElement)]),
 
342
  print_membership(NextElement, Membership, Coalesced_to).
 
343
-endif.