~rdoering/ubuntu/intrepid/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/hipe/opt/hipe_schedule.erl

  • Committer: Bazaar Package Importer
  • Author(s): Soren Hansen
  • Date: 2007-05-01 16:57:10 UTC
  • mfrom: (1.1.9 upstream)
  • Revision ID: james.westby@ubuntu.com-20070501165710-2sapk0hp2gf3o0ip
Tags: 1:11.b.4-2ubuntu1
* Merge with Debian Unstable. Remaining changes:
  - Add -fno-stack-protector to fix broken crypto_drv.
* DebianMaintainerField update.

Show diffs side-by-side

added added

removed removed

Lines of Context:
55
55
 
56
56
-include("../sparc/hipe_sparc.hrl").
57
57
 
58
 
%-define(debug1,true).
 
58
%%-define(debug1,true).
59
59
 
60
 
%-define(debug2,true).
61
 
-define(debug2,false).
 
60
-define(debug2(Str,Args),ok).
 
61
%%-define(debug2(Str,Args),io:format(Str,Args)).
62
62
 
63
63
-define(debug3(Str,Args),ok).
64
 
%-define(debug3(Str,Args),io:format(Str,Args)).
 
64
%%-define(debug3(Str,Args),io:format(Str,Args)).
65
65
 
66
 
%-define(debug4,true).
67
 
-define(debug4,false).
 
66
-define(debug4(Str,Args),ok).
 
67
%%-define(debug4(Str,Args),io:format(Str,Args)).
68
68
 
69
69
-define(debug5(Str,Args),ok).
70
 
%-define(debug5(Str,Args),io:format(Str,Args)).
 
70
%%-define(debug5(Str,Args),io:format(Str,Args)).
71
71
 
72
72
-define(debug(Str,Args),ok).
73
 
%-define(debug(Str,Args),io:format(Str,Args)).
 
73
%%-define(debug(Str,Args),io:format(Str,Args)).
74
74
 
75
75
 
76
76
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
190
190
%%               branches/jumps. If one is found fill_del tries to find
191
191
%%               an instr to fill the delayslot.
192
192
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
193
 
193
194
fill_delays(Sch, IxBlk, DAG) ->
194
195
    NewIxBlk =  hipe_vectors:list_to_vector(IxBlk),
195
 
%    NewSch   = hipe_vectors:list_to_vector(Sch),
 
196
    %% NewSch = hipe_vectors:list_to_vector(Sch),
196
197
    NewSch = fill_del(length(Sch), hipe_vectors:list_to_vector(Sch), 
197
198
                      NewIxBlk, DAG),
198
199
    {NewSch, NewIxBlk}.
208
209
%% Description : If a call/jump is found fill_branch_delay/fill_call_delay
209
210
%%                 is called to find a delay-filler.
210
211
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
212
 
211
213
fill_del(N, Sch, _IxBlk, _DAG) when N < 1 -> Sch;
212
214
fill_del(N, Sch, IxBlk, DAG) ->
213
215
    Index = get_index(Sch, N),
214
 
    case ?debug2 of 
215
 
        true -> 
216
 
            io:format("Index f�r ~p: ~p~n",[N, Index]),
217
 
            io:format("Instr: ~p~n", [get_instr(IxBlk, Index)]);
218
 
        false -> ok
219
 
    end,
 
216
    ?debug2("Index for ~p: ~p~nInstr: ~p~n",
 
217
            [N, Index, get_instr(IxBlk, Index)]),
220
218
    NewSch = 
221
219
        case get_instr(IxBlk, Index) of
222
220
            #call_link{} ->
248
246
%% Description : Searches backwards through the schedule trying to find an 
249
247
%%               instr without conflicts with the Call-instr.
250
248
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
249
 
251
250
fill_call_delay(Cand, _Call, Sch, _IxBlk, _DAG) when Cand < 1 -> Sch;
252
 
 
253
251
fill_call_delay(Cand, Call, Sch, IxBlk, DAG) ->
254
252
    CandIndex = get_index(Sch, Cand),
255
253
    CallIndex = get_index(Sch, Call),
264
262
                    CallI = get_instr(IxBlk, CallIndex),
265
263
                    
266
264
                    CandDefs = ordsets:from_list(hipe_sparc:defines(CandI)),
267
 
                    CandUses = ordsets:from_list(hipe_sparc:uses(CandI)),
268
 
                    CallDefs = ordsets:from_list(hipe_sparc:defines(CallI)),
 
265
                    %% CandUses = ordsets:from_list(hipe_sparc:uses(CandI)),
 
266
                    %% CallDefs = ordsets:from_list(hipe_sparc:defines(CallI)),
269
267
                    CallUses = ordsets:from_list(hipe_sparc:uses(CallI)),
270
268
                    
271
269
                    Args = case CallI of
280
278
                           end,
281
279
                    CallUses2 = ordsets:subtract(CallUses, Args),
282
280
                    Conflict = ordsets:intersection(CandDefs, CallUses2),
283
 
                    case ?debug2 of
284
 
                        true ->
285
 
                            io:format("single_depend -> true:~n ~p~n, ~p~n,~p~n",
286
 
                                      [CandI, CallI, DAG]),
287
 
                            io:format("Cand = ~p~nCall = ~p~n",[CandI,CallI]),
288
 
                            io:format("CandDefs = ~p~nCallDefs = ~p~n",[CandDefs,CallDefs]),
289
 
                            io:format("CandUses = ~p~nCallUses = ~p~n",[CandUses,CallUses]),
290
 
                            io:format("Args = ~p~nCallUses2 = ~p~n",[Args,CallUses2]),
291
 
                            
292
 
                            io:format("Conflict = ~p~n",[Conflict]);
293
 
                        false -> ok
294
 
                    end,
 
281
                    %% io:format("single_depend -> true:~n ~p~n, ~p~n,~p~n",[CandI,CallI,DAG]),
 
282
                    %% io:format("Cand = ~p~nCall = ~p~n",[CandI,CallI]),
 
283
                    %% io:format("CandDefs = ~p~nCallDefs = ~p~n",[CandDefs,CallDefs]),
 
284
                    %% io:format("CandUses = ~p~nCallUses = ~p~n",[CandUses,CallUses]),
 
285
                    %% io:format("Args = ~p~nCallUses2 = ~p~n",[Args,CallUses2]),
 
286
                    %% io:format("Conflict = ~p~n",[Conflict]),
295
287
                    
296
288
                    case Conflict of 
297
289
                        [] -> % No conflicts ==> Cand can fill delayslot after Call
316
308
%% Description : Searches backwards through the schedule trying to find an 
317
309
%%               instr without conflicts with the Branch-instr.
318
310
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
311
 
319
312
fill_branch_delay(Cand, _Br, Sch, _IxBlk, _DAG) when Cand < 1 -> Sch;
320
313
fill_branch_delay(Cand, Br, Sch, IxBlk, DAG) -> 
321
314
    CandIndex = get_index(Sch, Cand),
330
323
                true ->
331
324
                    BrI      = get_instr(IxBlk, BrIndex),
332
325
                    CandDefs = ordsets:from_list(hipe_sparc:defines(CandI)),
333
 
                    CandUses = ordsets:from_list(hipe_sparc:uses(CandI)),
334
 
                    BrDefs   = ordsets:from_list(hipe_sparc:defines(BrI)),
 
326
                    %% CandUses = ordsets:from_list(hipe_sparc:uses(CandI)),
 
327
                    %% BrDefs   = ordsets:from_list(hipe_sparc:defines(BrI)),
335
328
                    BrUses   = ordsets:from_list(hipe_sparc:uses(BrI)),
336
329
                    
337
330
                    Conflict = ordsets:intersection(CandDefs, BrUses),
338
 
                    case ?debug2 of
339
 
                        true ->
340
 
                            io:format("single_depend -> true: ~p~n, ~p~n,~p~n",
341
 
                                      [CandI, BrI, DAG]),
342
 
                            io:format("Cand = ~p~nBr = ~p~n",[CandI,BrI]),
343
 
                            io:format("CandDefs = ~p~nBrDefs = ~p~n",[CandDefs,BrDefs]),
344
 
                            io:format("CandUses = ~p~nBrUses = ~p~n",[CandUses,BrUses]),
345
 
                            io:format("Conflict = ~p~n",[Conflict]);
346
 
                        false -> ok
347
 
                    end,
 
331
                    %% io:format("single_depend -> true: ~p~n, ~p~n,~p~n", [CandI, BrI, DAG]),
 
332
                    %% io:format("Cand = ~p~nBr = ~p~n",[CandI,BrI]),
 
333
                    %% io:format("CandDefs = ~p~nBrDefs = ~p~n",[CandDefs,BrDefs]),
 
334
                    %% io:format("CandUses = ~p~nBrUses = ~p~n",[CandUses,BrUses]),
 
335
                    %% io:format("Conflict = ~p~n",[Conflict]);
348
336
                    
349
337
                    case Conflict of 
350
338
                        [] -> % No conflicts ==> 
489
477
    
490
478
    Prio = hipe_schedule_prio:init_instr_prio(N,DAG),
491
479
    Rsrc = init_resources(BigArray),
492
 
    case ?debug4 of
493
 
        true ->
494
 
            io:format("I_res: ~n~p~n",[I_res]),
495
 
            io:format("Prio: ~n~p~n",[Prio]),
496
 
            io:format("Rsrc: ~n~p~n",[Rsrc]);
497
 
        false -> ok
498
 
    end,
 
480
    ?debug4("I_res: ~n~p~nPrio: ~n~p~nRsrc: ~n~p~n", [I_res,Prio,Rsrc]),
499
481
    ?debug('cycle 1~n',[]),
500
482
    Sch = empty_schedule(),
501
483
    cycle_sched(1,Ready,DAG,Preds,Earliest,Rsrc,I_res,Prio,Sch,N,IxBlk).