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

« back to all changes in this revision

Viewing changes to lib/hipe/rtl/hipe_rtl_mk_switch.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:
18
18
%%              * 2001-07-30 EJ (happi@csd.uu.se):
19
19
%%               Fixed some bugs and started cleanup.
20
20
%%  CVS      :
21
 
%%              $Author: richardc $
22
 
%%              $Date: 2002/10/01 12:44:28 $
23
 
%%              $Revision: 1.10 $
 
21
%%              $Author: kostis $
 
22
%%              $Date: 2006/07/24 16:34:36 $
 
23
%%              $Revision: 1.21 $
24
24
%% ====================================================================
25
25
%%  Exports  :
26
 
%%    gen_switch_val(I, VarMap, ConstTab, Options, ExitInfo)
27
 
%%    gen_switch_tuple(I, Map, ConstTab, Options, ExitInfo)
 
26
%%    gen_switch_val(I, VarMap, ConstTab, Options)
 
27
%%    gen_switch_tuple(I, Map, ConstTab, Options)
28
28
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
29
29
 
30
30
-module(hipe_rtl_mk_switch).
31
 
-export([gen_switch_val/5,gen_switch_tuple/5]).
 
31
-export([gen_switch_val/4,gen_switch_tuple/4]).
 
32
 
32
33
%%-------------------------------------------------------------------------
 
34
 
33
35
-include("../main/hipe.hrl").
 
36
 
34
37
%%-------------------------------------------------------------------------
 
38
 
35
39
-define(MINFORJUMPTABLE,9).
36
40
        % Minimum number of integers needed to use something else than an inline search.
37
41
-define(MINFORINTSEARCHTREE,65).  % Must be at least 3
48
52
-define(MAXINLINEATOMSEARCH,64). % Must be at least 3
49
53
        % The cutoff point between inlined and non-inlined binary search for atoms
50
54
 
51
 
-define(WORDSIZE, 4).
 
55
-define(WORDSIZE, hipe_rtl_arch:word_size()).
52
56
-define(MINDENSITY, 0.5).
53
57
        % Minimum density required to use a jumptable instead of a binary search.
54
58
 
60
64
%% Options used by this module:
61
65
%%
62
66
%% [no_]use_indexing
63
 
%%    Determines if any indexing be should be done at all. Turned on by default at 
64
 
%%    optimization level o2 and higher.
 
67
%%    Determines if any indexing be should be done at all. Turned on
 
68
%%    by default at optimization level o2 and higher.
 
69
%%
65
70
%% [no_]use_clusters
66
 
%%    Controls whether we attempt to divide sparse integer switches into smaller
67
 
%%    dense clusters for which jumptables are practical. Turned off by
68
 
%%    default since it can increase compilation time considerably and
69
 
%%    most programs will gain little benefit from it.
 
71
%%    Controls whether we attempt to divide sparse integer switches
 
72
%%    into smaller dense clusters for which jumptables are practical.
 
73
%%    Turned off by default since it can increase compilation time
 
74
%%    considerably and most programs will gain little benefit from it.
 
75
%%
70
76
%% [no_]use_inline_atom_search
71
 
%%    Controls whether we use an inline binary search for small number of atoms.
72
 
%%    Turned off by default since this is currently only supported on sparc 
73
 
%%    (and not on x86) and probably needs a bit more testing before it
74
 
%%    can be turned on by default.
 
77
%%    Controls whether we use an inline binary search for small number
 
78
%%    of atoms. Turned off by default since this is currently only
 
79
%%    supported on SPARC (and not on x86) and probably needs a bit
 
80
%%    more testing before it can be turned on by default.
75
81
 
76
 
gen_switch_val(I, VarMap, ConstTab, Options, ExitInfo) ->
 
82
gen_switch_val(I, VarMap, ConstTab, Options) ->
77
83
  case proplists:get_bool(use_indexing, Options) of
78
 
    false -> gen_slow_switch_val(I, VarMap, ConstTab, Options, ExitInfo);
79
 
    true -> gen_fast_switch_val(I, VarMap, ConstTab, Options, ExitInfo)
 
84
    false -> gen_slow_switch_val(I, VarMap, ConstTab, Options);
 
85
    true -> gen_fast_switch_val(I, VarMap, ConstTab, Options)
80
86
  end.
81
87
 
82
 
gen_fast_switch_val(I, VarMap, ConstTab, Options, ExitInfo) ->
 
88
gen_fast_switch_val(I, VarMap, ConstTab, Options) ->
83
89
  {Arg, VarMap0} = 
84
 
        hipe_rtl_varmap:icode_var2rtl_var(hipe_icode:switch_val_arg(I), VarMap),
 
90
    hipe_rtl_varmap:icode_var2rtl_var(hipe_icode:switch_val_arg(I), VarMap),
85
91
  IcodeFail = hipe_icode:switch_val_fail_label(I),
86
92
  {Fail, VarMap1} = hipe_rtl_varmap:icode_label2rtl_label(IcodeFail, VarMap0),
87
93
  %% Important that the list of cases is sorted when handling integers.
92
98
  %% This check is currently not really necessary.  The checking
93
99
  %% happens at an earlier phase of the compilation.
94
100
  {Types, InitCode} = split_types(Cases, Arg),
95
 
  handle_types(Types, InitCode, VarMap1, ConstTab, Arg, {I, Fail, Options, ExitInfo}).
96
 
 
97
 
handle_types([{Type, Lbl, Cases}| Types], Code, VarMap, ConstTab, Arg,
98
 
             Info) ->
99
 
 
 
101
  handle_types(Types, InitCode, VarMap1, ConstTab, Arg, {I, Fail, Options}).
 
102
 
 
103
handle_types([{Type,Lbl,Cases}|Types], Code, VarMap, ConstTab, Arg, Info) ->
100
104
  {Code1,VarMap1,ConstTab1} = gen_fast_switch_on(Type, Cases, 
101
105
                                                 VarMap, 
102
106
                                                 ConstTab, Arg, Info),
103
 
 
104
107
  handle_types(Types, [Code,Lbl,Code1], VarMap1, ConstTab1, Arg, Info);
105
108
handle_types([], Code, VarMap, ConstTab, _, _) ->
106
109
  {Code, VarMap, ConstTab}.
107
110
 
108
111
 
109
 
gen_fast_switch_on(integer, Cases, VarMap, ConstTab, Arg, {I, Fail, Options, _ExitInfo})  ->
 
112
gen_fast_switch_on(integer, Cases, VarMap, ConstTab, Arg, {I, Fail, Options})  ->
110
113
  {First,_} = hd(Cases),
111
114
  Min = hipe_icode:const_value(First),
112
115
  if length(Cases) < ?MINFORJUMPTABLE ->
129
132
          find_cluster(CM,VarMap,ConstTab,Options,Arg,Fail,hipe_icode:switch_val_fail_label(I))
130
133
      end
131
134
  end;
132
 
gen_fast_switch_on(atom, Cases, VarMap, ConstTab, Arg, {_I, Fail, Options, _ExitInfo})  ->
 
135
gen_fast_switch_on(atom, Cases, VarMap, ConstTab, Arg, {_I, Fail, Options})  ->
133
136
  case proplists:get_bool(use_inline_atom_search, Options) of
134
137
    true ->
135
138
      if
147
150
          gen_search_switch_val(Arg, Cases, Fail, VarMap, ConstTab, Options)
148
151
      end
149
152
  end;  
150
 
gen_fast_switch_on(_, _Cases, VarMap, ConstTab, _Arg, {I, _Fail, Options, ExitInfo})  ->
 
153
gen_fast_switch_on(_, _, VarMap, ConstTab, _, {I,_Fail,Options})  ->
151
154
  %% We can only handle smart indexing of integers and atoms
152
155
  %% TODO: Consider bignum
153
 
  gen_slow_switch_val(I, VarMap, ConstTab, Options, ExitInfo).
 
156
  gen_slow_switch_val(I, VarMap, ConstTab, Options).
154
157
 
155
158
 
156
159
%% Split different types into separate switches.
162
165
  %% Cant happen.
163
166
  ?EXIT({empty_caselist}).
164
167
 
165
 
switch_on_types([{Type, Cases}], AccCode, AccCases, _Arg) ->
 
168
switch_on_types([{Type,Cases}], AccCode, AccCases, _Arg) ->
166
169
  Lbl = hipe_rtl:mk_new_label(),
167
170
  I = hipe_rtl:mk_goto(hipe_rtl:label_name(Lbl)),
168
 
  {[{Type, Lbl, lists:reverse(Cases)}| AccCases],lists:reverse([I|AccCode])};
169
 
switch_on_types([{other, Cases}| Rest], AccCode, AccCases, Arg) ->
 
171
  {[{Type,Lbl,lists:reverse(Cases)} | AccCases], lists:reverse([I|AccCode])};
 
172
switch_on_types([{other,Cases} | Rest], AccCode, AccCases, Arg) ->
170
173
  %% Make sure the general case is handled last.
171
 
  switch_on_types([Rest ++ {other, Cases}], AccCode, AccCases, Arg);
172
 
 
173
 
switch_on_types([{Type, Cases}| Rest], AccCode, AccCases, Arg) ->
 
174
  switch_on_types(Rest ++ [{other,Cases}], AccCode, AccCases, Arg);
 
175
switch_on_types([{Type,Cases} | Rest], AccCode, AccCases, Arg) ->
174
176
  TLab = hipe_rtl:mk_new_label(),
175
177
  FLab = hipe_rtl:mk_new_label(),
176
178
  TestCode = 
180
182
                                   hipe_rtl:label_name(FLab), 0.5);
181
183
      atom ->
182
184
        hipe_tagscheme:test_atom(Arg, hipe_rtl:label_name(TLab), 
183
 
                                   hipe_rtl:label_name(FLab), 0.5);
 
185
                                 hipe_rtl:label_name(FLab), 0.5);
184
186
      bignum ->
185
187
        hipe_tagscheme:test_bignum(Arg, hipe_rtl:label_name(TLab), 
186
188
                                   hipe_rtl:label_name(FLab), 0.5);
187
189
      _ -> ?EXIT({ooops, type_not_handled, Type})
188
190
    end,
189
 
        
190
 
  switch_on_types(Rest, [[TestCode, FLab]|AccCode], 
191
 
                  [{Type, TLab, lists:reverse(Cases)}|AccCases],Arg).
 
191
  switch_on_types(Rest, [[TestCode,FLab] | AccCode],
 
192
                  [{Type,TLab,lists:reverse(Cases)} | AccCases], Arg).
192
193
 
193
194
split([Case|Cases], Type, Current, Rest) ->
194
195
  case casetype(Case) of
203
204
%% Determine what type an entry in the caselist has
204
205
 
205
206
casetype({Const,_}) ->
206
 
        casetype(hipe_icode:const_value(Const));
 
207
  casetype(hipe_icode:const_value(Const));
207
208
casetype(A) ->
208
 
        if
209
 
          is_integer(A) -> 
210
 
            case hipe_tagscheme:is_fixnum(A) of
211
 
              true -> integer;
212
 
              false -> bignum
213
 
            end;
214
 
          is_float(A) -> float;
215
 
          is_atom(A) -> atom;
216
 
          true -> other
217
 
        end.
218
 
 
 
209
  if
 
210
    is_integer(A) -> 
 
211
      case hipe_tagscheme:is_fixnum(A) of
 
212
        true -> integer;
 
213
        false -> bignum
 
214
      end;
 
215
    is_float(A) -> float;
 
216
    is_atom(A) -> atom;
 
217
    true -> other
 
218
  end.
219
219
 
220
220
%% check that no duplicate values occur in the case list and also
221
221
%% check that all case values have the same type.
222
222
check_duplicates([]) -> true;
223
223
check_duplicates([_]) -> true;
224
224
check_duplicates([{Const1,_},{Const2,L2}|T]) ->
225
 
        C1 = hipe_icode:const_value(Const1),
226
 
        C2 = hipe_icode:const_value(Const2),
227
 
%%      T1 = casetype(C1),
228
 
%%      T2 = casetype(C2),
229
 
        if C1 =/= C2 -> %% , T1 =:= T2 ->
230
 
                check_duplicates([{Const2,L2}|T]);
231
 
           true ->
232
 
                ?EXIT({bad_values_in_switchval,C1})
233
 
        end.    
 
225
  C1 = hipe_icode:const_value(Const1),
 
226
  C2 = hipe_icode:const_value(Const2),
 
227
  %%    T1 = casetype(C1),
 
228
  %%    T2 = casetype(C2),
 
229
  if C1 =/= C2 -> %% , T1 =:= T2 ->
 
230
      check_duplicates([{Const2,L2}|T]);
 
231
     true ->
 
232
      ?EXIT({bad_values_in_switchval,C1})
 
233
  end.
234
234
 
235
235
%%
236
236
%% Determine the optimal way to divide Cases into clusters such that each 
253
253
%% each cluster is dense.
254
254
 
255
255
minclusters(Cases) when is_list(Cases) ->
256
 
        minclusters(list_to_tuple(Cases));
 
256
  minclusters(list_to_tuple(Cases));
257
257
minclusters(Cases) when is_tuple(Cases) ->
258
 
        N = size(Cases),
259
 
        MinClusters = list_to_tuple([0|n_list(N,inf)]),
260
 
        i_loop(1,N,MinClusters,Cases).
 
258
  N = size(Cases),
 
259
  MinClusters = list_to_tuple([0|n_list(N,inf)]),
 
260
  i_loop(1,N,MinClusters,Cases).
261
261
 
262
262
%% Create a list with N elements initialized to Init
263
263
n_list(0,_) -> [];
264
264
n_list(N,Init) -> [Init | n_list(N-1,Init)].
265
265
 
266
266
 
267
 
 
268
267
%% Do the dirty work of minclusters
269
268
i_loop(I,N,MinClusters,_Cases) when I > N -> 
270
 
        MinClusters;
 
269
  MinClusters;
271
270
i_loop(I,N,MinClusters,Cases) when I =< N ->
272
 
        M = j_loop(0, I-1, MinClusters, Cases),
273
 
        i_loop(I+1, N, M, Cases).
 
271
  M = j_loop(0, I-1, MinClusters, Cases),
 
272
  i_loop(I+1, N, M, Cases).
274
273
 
275
274
%% More dirty work      
276
275
j_loop(J,I1,MinClusters,_Cases) when J > I1 ->
277
 
        MinClusters;
 
276
  MinClusters;
278
277
j_loop(J,I1,MinClusters,Cases) when J =< I1 ->
279
 
        D = density(Cases,J+1,I1+1),
280
 
        A0 = element(J+1,MinClusters),
281
 
        A = if
282
 
                is_number(A0) ->
283
 
                        A0+1;
284
 
                true ->
285
 
                        A0
286
 
        end,
287
 
        B = element(I1+2,MinClusters),
288
 
        M = if
289
 
                D >= ?MINDENSITY, A<B ->
290
 
                        setelement(I1+2,MinClusters,A);
291
 
                true ->
292
 
                        MinClusters
293
 
        end,
294
 
        j_loop(J+1,I1,M,Cases).
295
 
                
 
278
  D = density(Cases,J+1,I1+1),
 
279
  A0 = element(J+1,MinClusters),
 
280
  A = if
 
281
        is_number(A0) ->
 
282
          A0+1;
 
283
        true ->
 
284
          A0
 
285
      end,
 
286
  B = element(I1+2,MinClusters),
 
287
  M = if
 
288
        D >= ?MINDENSITY, A<B ->
 
289
          setelement(I1+2,MinClusters,A);
 
290
        true ->
 
291
          MinClusters
 
292
      end,
 
293
  j_loop(J+1,I1,M,Cases).
 
294
 
296
295
 
297
296
%% Determine the density of a (subset of a) case list
298
297
%% A is a tuple with the cases in order from smallest to largest
299
298
%% I is the index of the first element and J of the last
300
299
 
301
300
density(A,I,J) ->
302
 
        {AI,_}=element(I,A),
303
 
        {AJ,_}=element(J,A),
304
 
        (J-I+1)/(hipe_icode:const_value(AJ)-hipe_icode:const_value(AI)+1).
 
301
  {AI,_} = element(I,A),
 
302
  {AJ,_} = element(J,A),
 
303
  (J-I+1)/(hipe_icode:const_value(AJ)-hipe_icode:const_value(AI)+1).
305
304
 
306
305
 
307
306
%% Split a case list into dense clusters
308
307
%% Returns a list of lists of cases.
309
 
%% Cases is the case list and Clust is a list describing the optimal clustering
310
 
%% as returned by minclusters
311
 
%%
312
 
%% If the value in the last place in minclusters is M then we can split the case
313
 
%% list into M clusters. We then search for the last (== right-most) occurance of
314
 
%% the value M-1 in minclusters. That indicates the largest number of cases that 
315
 
%% can be split into M-1 clusters. This means that the cases in between constitute
316
 
%% one cluster. Then we recurse on the remainder of the cases.
317
 
%%
318
 
%% The various calls to lists:reverse are just to ensure that the cases remain in
319
 
%% the correct, sorted order.
 
308
%%
 
309
%% Cases is the case list and Clust is a list describing the optimal
 
310
%% clustering as returned by minclusters
 
311
%%
 
312
%% If the value in the last place in minclusters is M then we can
 
313
%% split the case list into M clusters. We then search for the last
 
314
%% (== right-most) occurance of the value M-1 in minclusters. That
 
315
%% indicates the largest number of cases that can be split into M-1
 
316
%% clusters. This means that the cases in between constitute one
 
317
%% cluster. Then we recurse on the remainder of the cases.
 
318
%%
 
319
%% The various calls to lists:reverse are just to ensure that the
 
320
%% cases remain in the correct, sorted order.
320
321
 
321
322
cluster_split(Cases,Clust) ->
322
 
        A=tl(tuple_to_list(Clust)),
323
 
        Max = element(size(Clust),Clust),
324
 
        L1=lists:reverse(Cases),
325
 
        L2=lists:reverse(A),
326
 
        cluster_split(Max,[],[],L1,L2).
 
323
  A = tl(tuple_to_list(Clust)),
 
324
  Max = element(size(Clust),Clust),
 
325
  L1 = lists:reverse(Cases),
 
326
  L2 = lists:reverse(A),
 
327
  cluster_split(Max,[],[],L1,L2).
327
328
 
328
329
cluster_split(0,[],Res,Cases,_Clust) -> 
329
 
        L=lists:reverse(Cases),
330
 
        {H,_}=hd(L),
331
 
        {T,_}=hd(Cases),
332
 
        [{dense,hipe_icode:const_value(H),hipe_icode:const_value(T),L}|Res];
 
330
  L = lists:reverse(Cases),
 
331
  {H,_} = hd(L),
 
332
  {T,_} = hd(Cases),
 
333
  [{dense,hipe_icode:const_value(H),hipe_icode:const_value(T),L}|Res];
333
334
 
334
335
cluster_split(N,[],Res,Cases,[N|Clust]) -> 
335
 
        cluster_split(N-1,[],Res,Cases,[N|Clust]);
 
336
  cluster_split(N-1,[],Res,Cases,[N|Clust]);
336
337
 
337
338
cluster_split(N,Sofar,Res,Cases,[N|Clust]) -> 
338
 
        {H,_}=hd(Sofar),
339
 
        {T,_}=lists:last(Sofar),
340
 
        cluster_split(N-1,[],[{dense,hipe_icode:const_value(H),hipe_icode:const_value(T),Sofar}|Res],Cases,[N|Clust]);
 
339
  {H,_} = hd(Sofar),
 
340
  {T,_} = lists:last(Sofar),
 
341
  cluster_split(N-1,[],[{dense,hipe_icode:const_value(H),hipe_icode:const_value(T),Sofar}|Res],Cases,[N|Clust]);
341
342
 
342
343
cluster_split(N,Sofar,Res,[C|Cases],[_|Clust]) ->
343
 
        cluster_split(N,[C|Sofar],Res,Cases,Clust).
344
 
 
 
344
  cluster_split(N,[C|Sofar],Res,Cases,Clust).
345
345
 
346
346
%%
347
347
%% Merge adjacent small clusters into larger sparse clusters
349
349
cluster_merge([C]) -> [C];
350
350
 
351
351
cluster_merge([{dense,Min,Max,C}|T]) when length(C) >= ?MINFORJUMPTABLE ->
352
 
        C2=cluster_merge(T),
353
 
        [{dense,Min,Max,C}|C2];
 
352
  C2 = cluster_merge(T),
 
353
  [{dense,Min,Max,C}|C2];
354
354
 
355
355
cluster_merge([{sparse,Min,_,C},{sparse,_,Max,D}|T]) ->
356
 
        R = {sparse,Min,Max,C ++ D},
357
 
        cluster_merge([R|T]);
 
356
  R = {sparse,Min,Max,C ++ D},
 
357
  cluster_merge([R|T]);
358
358
 
359
359
cluster_merge([{sparse,Min,_,C},{dense,_,Max,D}|T]) when length(D) < ?MINFORJUMPTABLE ->
360
 
        R = {sparse,Min,Max,C ++ D},
361
 
        cluster_merge([R|T]);
 
360
  R = {sparse,Min,Max,C ++ D},
 
361
  cluster_merge([R|T]);
362
362
 
363
363
cluster_merge([{dense,Min,_,C},{dense,_,Max,D}|T]) when length(C) < ?MINFORJUMPTABLE, length(D) < ?MINFORJUMPTABLE ->
364
 
        R = {sparse,Min,Max,C ++ D},
365
 
        cluster_merge([R|T]);
 
364
  R = {sparse,Min,Max,C ++ D},
 
365
  cluster_merge([R|T]);
366
366
 
367
367
cluster_merge([{dense,Min,_,D},{sparse,_,Max,C}|T]) when length(D) < ?MINFORJUMPTABLE ->
368
 
        R = {sparse,Min,Max,C ++ D},
369
 
        cluster_merge([R|T]);
 
368
  R = {sparse,Min,Max,C ++ D},
 
369
  cluster_merge([R|T]);
370
370
 
371
371
cluster_merge([A,{dense,Min,Max,C}|T]) when length(C) >= ?MINFORJUMPTABLE ->
372
 
        R=cluster_merge([{dense,Min,Max,C}|T]),
373
 
        [A|R].
 
372
  R = cluster_merge([{dense,Min,Max,C}|T]),
 
373
  [A|R].
374
374
 
375
375
 
376
376
%% Generate code to search for the correct cluster
377
377
 
378
378
find_cluster([{sparse,_Min,_Max,C}],VarMap,ConstTab,Options,Arg,Fail,_IcodeFail) ->
379
 
        case length(C) < ?MINFORINTSEARCHTREE of
380
 
           true ->
381
 
                gen_small_switch_val(Arg,C,Fail,VarMap,ConstTab,Options);
382
 
           _ ->
383
 
                gen_search_switch_val(Arg,C,Fail,VarMap,ConstTab,Options)
384
 
        end;
385
 
 
386
 
        
 
379
  case length(C) < ?MINFORINTSEARCHTREE of
 
380
    true ->
 
381
      gen_small_switch_val(Arg,C,Fail,VarMap,ConstTab,Options);
 
382
    _ ->
 
383
      gen_search_switch_val(Arg,C,Fail,VarMap,ConstTab,Options)
 
384
  end;
387
385
find_cluster([{dense,Min,_Max,C}],VarMap,ConstTab,Options,Arg,Fail,IcodeFail) ->        
388
 
        case length(C) < ?MINFORJUMPTABLE of
389
 
           true ->
390
 
                gen_small_switch_val(Arg,C,Fail,VarMap,ConstTab,Options);
391
 
           _ ->
392
 
                gen_jump_table(Arg,Fail,IcodeFail,VarMap,ConstTab,C,Min)
393
 
        end;
394
 
 
395
 
        
 
386
  case length(C) < ?MINFORJUMPTABLE of
 
387
    true ->
 
388
      gen_small_switch_val(Arg,C,Fail,VarMap,ConstTab,Options);
 
389
    _ ->
 
390
      gen_jump_table(Arg,Fail,IcodeFail,VarMap,ConstTab,C,Min)
 
391
  end;
396
392
find_cluster([{Density,Min,Max,C}|T],VarMap,ConstTab,Options,Arg,Fail,IcodeFail) ->
397
 
        
398
 
        ClustLab=hipe_rtl:mk_new_label(),
399
 
        NextLab=hipe_rtl:mk_new_label(),
400
 
        {ClustCode,V1,C1}=find_cluster([{Density,Min,Max,C}],VarMap,ConstTab,Options,Arg,Fail,IcodeFail),
401
 
 
402
 
        {Rest,V2,C2}=find_cluster(T,V1,C1,Options,Arg,Fail,IcodeFail),
403
 
 
404
 
        {[
405
 
        hipe_rtl:mk_branch(Arg , gt, hipe_rtl:mk_imm(hipe_tagscheme:mk_fixnum(Max)),
406
 
                        hipe_rtl:label_name(NextLab), 
407
 
                        hipe_rtl:label_name(ClustLab) , 0.50),  
408
 
        ClustLab
409
 
        ] ++    
410
 
        ClustCode ++
411
 
        [NextLab] ++
412
 
        Rest,
413
 
        V2,C2}.
414
 
 
 
393
  ClustLab = hipe_rtl:mk_new_label(),
 
394
  NextLab = hipe_rtl:mk_new_label(),
 
395
  {ClustCode,V1,C1} = find_cluster([{Density,Min,Max,C}],VarMap,ConstTab,Options,Arg,Fail,IcodeFail),
 
396
 
 
397
  {Rest,V2,C2} = find_cluster(T,V1,C1,Options,Arg,Fail,IcodeFail),
 
398
  
 
399
  {[
 
400
    hipe_rtl:mk_branch(Arg, gt, hipe_rtl:mk_imm(hipe_tagscheme:mk_fixnum(Max)),
 
401
                       hipe_rtl:label_name(NextLab), 
 
402
                       hipe_rtl:label_name(ClustLab), 0.50),    
 
403
    ClustLab
 
404
   ] ++ 
 
405
   ClustCode ++
 
406
   [NextLab] ++
 
407
   Rest,
 
408
   V2,C2}.
415
409
 
416
410
%% Generate efficient code for a linear search through the case list.
417
411
%% Only works for atoms and integer.
418
412
gen_linear_switch_val(Arg,Cases,Fail,VarMap,ConstTab,_Options) ->
419
 
        {Values,_Labels} = split_cases(Cases),
420
 
        {LabMap,VarMap1} = lbls_from_cases(Cases,VarMap),
421
 
        
422
 
        Code = fast_linear_search(Arg,Values,LabMap,Fail),
423
 
        {Code,VarMap1,ConstTab}.
 
413
  {Values,_Labels} = split_cases(Cases),
 
414
  {LabMap,VarMap1} = lbls_from_cases(Cases,VarMap),
 
415
  Code = fast_linear_search(Arg,Values,LabMap,Fail),
 
416
  {Code,VarMap1,ConstTab}.
424
417
 
425
418
fast_linear_search(_Arg,[],[],Fail) ->
426
 
        [
427
 
        hipe_rtl:mk_goto(hipe_rtl:label_name(Fail))
428
 
        ];
 
419
  [hipe_rtl:mk_goto(hipe_rtl:label_name(Fail))];
429
420
fast_linear_search(Arg,[Case|Cases],[Label|Labels],Fail) ->
430
 
        Reg= hipe_rtl:mk_new_reg(),
431
 
        NextLab = hipe_rtl:mk_new_label(),
432
 
        C2 = fast_linear_search(Arg,Cases,Labels,Fail),
433
 
        C1 =
434
 
          if
435
 
            is_integer(Case) ->
436
 
                TVal= hipe_tagscheme:mk_fixnum(Case),
437
 
                [
438
 
                hipe_rtl:mk_move(Reg,hipe_rtl:mk_imm(TVal)),
439
 
                hipe_rtl:mk_branch(Arg,eq,Reg,
440
 
                                Label,
441
 
                                hipe_rtl:label_name(NextLab), 0.5),
442
 
                NextLab
443
 
                ];
444
 
            is_atom(Case) ->
445
 
                [
446
 
                hipe_rtl:mk_load_atom(Reg,Case),
447
 
                hipe_rtl:mk_branch(Arg,eq,Reg,
448
 
                                Label,
449
 
                                hipe_rtl:label_name(NextLab), 0.5),
450
 
                NextLab
451
 
                ];
452
 
            true ->   % This should never happen !
453
 
                ?EXIT({internal_error_in_switch_val,Case})
454
 
          end,
455
 
        [C1,C2].
 
421
  Reg = hipe_rtl:mk_new_reg_gcsafe(),
 
422
  NextLab = hipe_rtl:mk_new_label(),
 
423
  C2 = fast_linear_search(Arg,Cases,Labels,Fail),
 
424
  C1 =
 
425
    if
 
426
      is_integer(Case) ->
 
427
        TVal = hipe_tagscheme:mk_fixnum(Case),
 
428
        [
 
429
         hipe_rtl:mk_move(Reg,hipe_rtl:mk_imm(TVal)),
 
430
         hipe_rtl:mk_branch(Arg,eq,Reg,
 
431
                            Label,
 
432
                            hipe_rtl:label_name(NextLab), 0.5),
 
433
         NextLab
 
434
        ];
 
435
      is_atom(Case) ->
 
436
        [
 
437
         hipe_rtl:mk_load_atom(Reg,Case),
 
438
         hipe_rtl:mk_branch(Arg,eq,Reg,
 
439
                            Label,
 
440
                            hipe_rtl:label_name(NextLab), 0.5),
 
441
         NextLab
 
442
        ];
 
443
      true ->   % This should never happen !
 
444
        ?EXIT({internal_error_in_switch_val,Case})
 
445
    end,
 
446
  [C1,C2].
456
447
 
457
448
 
458
449
%% Generate code to search through a small cluster of integers using
459
450
%% binary search
460
451
gen_small_switch_val(Arg,Cases,Fail,VarMap,ConstTab,_Options) -> 
461
 
        {Values,_Labels} = split_cases(Cases),
462
 
        {LabMap,VarMap1} = lbls_from_cases(Cases,VarMap),
463
 
        Keys = [hipe_tagscheme:mk_fixnum(X)    % Add tags to the values
464
 
                || X <- Values],
465
 
        Code = inline_search(Keys, LabMap, Arg, Fail),
466
 
        {Code, VarMap1, ConstTab}.
 
452
  {Values,_Labels} = split_cases(Cases),
 
453
  {LabMap,VarMap1} = lbls_from_cases(Cases,VarMap),
 
454
  Keys = [hipe_tagscheme:mk_fixnum(X)    % Add tags to the values
 
455
          || X <- Values],
 
456
  Code = inline_search(Keys, LabMap, Arg, Fail),
 
457
  {Code, VarMap1, ConstTab}.
467
458
 
468
459
 
469
460
%% Generate code to search through a small cluster of atoms
470
461
gen_atom_switch_val(Arg,Cases,Fail,VarMap,ConstTab,_Options) -> 
471
 
        {Values, _Labels} = split_cases(Cases),
472
 
        {LabMap,VarMap1} = lbls_from_cases(Cases,VarMap),
473
 
        LMap = [{label,L} || L <- LabMap],
474
 
        
475
 
        {NewConstTab,Id} = hipe_consttab:insert_sorted_block(ConstTab, Values),
476
 
        {NewConstTab2,LabId} = hipe_consttab:insert_sorted_block(NewConstTab, 4 , word, LMap, Values),
477
 
 
478
 
        Code = inline_atom_search(0, length(Cases)-1, Id, LabId, Arg, Fail, LabMap),
479
 
        
480
 
        {Code, VarMap1, NewConstTab2}.
481
 
 
482
 
 
483
 
%% calculate the middle position of a list (+ 1 because of 1-indexing of listes)
 
462
  {Values, _Labels} = split_cases(Cases),
 
463
  {LabMap,VarMap1} = lbls_from_cases(Cases,VarMap),
 
464
  LMap = [{label,L} || L <- LabMap],
 
465
  
 
466
  {NewConstTab,Id} = hipe_consttab:insert_sorted_block(ConstTab, Values),
 
467
  {NewConstTab2,LabId} =
 
468
    hipe_consttab:insert_sorted_block(NewConstTab, word, LMap, Values),
 
469
  
 
470
  Code = inline_atom_search(0, length(Cases)-1, Id, LabId, Arg, Fail, LabMap),
 
471
  
 
472
  {Code, VarMap1, NewConstTab2}.
 
473
 
 
474
 
 
475
%% calculate the middle position of a list (+ 1 because of 1-indexing of lists)
484
476
get_middle(List) ->
485
 
    N = length(List),
486
 
    N div 2 + 1.
487
 
 
 
477
  N = length(List),
 
478
  N div 2 + 1.
488
479
 
489
480
%% get element [N1, N2] from a list
490
481
get_cases(_, 0, 0) ->
491
 
     [];
 
482
  [];
492
483
get_cases([H|T], 0, N) ->
493
 
    [H | get_cases(T, 0, N - 1)];
 
484
  [H | get_cases(T, 0, N - 1)];
494
485
get_cases([_|T], N1, N2) ->
495
 
    get_cases(T, N1 - 1, N2 - 1).
496
 
 
497
 
    
498
 
 
499
 
%% inline_search/4 creates rtl code for a inlined binary search.
 
486
  get_cases(T, N1 - 1, N2 - 1).
 
487
 
 
488
 
 
489
%% inline_search/4 creates RTL code for a inlined binary search.
500
490
%% It requires two sorted tables - one with the keys to search
501
491
%% through and one with the corresponding labels to jump to.
502
492
%%    
509
499
 
510
500
inline_search([], _LabelList, _KeyReg, _Default) -> [];
511
501
inline_search(KeyList, LabelList, KeyReg, Default) ->
512
 
    %% Create some registers and lables that we need.
513
 
    Reg = hipe_rtl:mk_new_reg(),
514
 
    Lab1 = hipe_rtl:mk_new_label(),
515
 
    Lab2 = hipe_rtl:mk_new_label(),
516
 
    Lab3 = hipe_rtl:mk_new_label(),
517
 
 
518
 
    Length = length(KeyList),
519
 
 
520
 
    if
521
 
        Length >= 3 ->
522
 
 
523
 
            %% Get middle element and keys/labels before that and after
524
 
            Middle_pos = get_middle(KeyList),
525
 
            Middle_key = lists:nth(Middle_pos, KeyList),
526
 
            Keys_beginning = get_cases(KeyList, 0, Middle_pos - 1),
527
 
            Labels_beginning = get_cases(LabelList, 0, Middle_pos - 1),
528
 
            Keys_ending = get_cases(KeyList, Middle_pos, Length),
529
 
            Labels_ending = get_cases(LabelList, Middle_pos, Length),
530
 
 
531
 
            %% Create the code.
532
 
 
533
 
            %% Get the label and build it up properly
534
 
            Middle_label = lists:nth(Middle_pos, LabelList),
535
 
 
536
 
            A =[hipe_rtl:mk_move(Reg, hipe_rtl:mk_imm(Middle_key)),
537
 
                hipe_rtl:mk_branch(KeyReg, lt, Reg, 
538
 
                                        hipe_rtl:label_name(Lab2), 
539
 
                                        hipe_rtl:label_name(Lab1), 0.5),
540
 
                Lab1,
541
 
                hipe_rtl:mk_branch(KeyReg, gt, Reg,
542
 
                                        hipe_rtl:label_name(Lab3), 
543
 
                                        Middle_label , 0.5),
544
 
                Lab2],
545
 
            %% build search tree for keys less than the middle element
546
 
            B = inline_search(Keys_beginning, Labels_beginning, KeyReg, Default),
547
 
            %% ...and for keys bigger than the middle element
548
 
            D = inline_search(Keys_ending, Labels_ending, KeyReg, Default),
549
 
 
550
 
            %% append the code and return it
551
 
            A ++ B ++ [Lab3] ++ D;
552
 
 
553
 
        Length == 2 ->
554
 
            %% get the first and second elements and theirs labels
555
 
            Key_first = hd(KeyList),
556
 
            First_label = hd(LabelList),
557
 
 
558
 
            % Key_second = hipe_tagscheme:mk_fixnum(lists:nth(2, KeyList)),
559
 
            Key_second = lists:nth(2, KeyList),
560
 
            Second_label = lists:nth(2, LabelList),
561
 
 
562
 
            NewLab = hipe_rtl:mk_new_label(),
563
 
 
564
 
            %% compare them
565
 
            A = [hipe_rtl:mk_move(Reg,hipe_rtl:mk_imm(Key_first)),
566
 
                 hipe_rtl:mk_branch(KeyReg, eq, Reg,
567
 
                                    First_label, 
568
 
                                    hipe_rtl:label_name(NewLab) , 0.5),
569
 
 
570
 
                 NewLab],
571
 
                 
572
 
            B = [hipe_rtl:mk_move(Reg,hipe_rtl:mk_imm(Key_second)),
573
 
                 hipe_rtl:mk_branch(KeyReg, eq, Reg,
574
 
                                    Second_label, 
575
 
                                    hipe_rtl:label_name(Default) , 0.5)],
576
 
            A ++ B;
577
 
 
578
 
        Length == 1 ->
579
 
            Key = hd(KeyList),
580
 
            Label = hd(LabelList),
581
 
 
582
 
            [hipe_rtl:mk_move(Reg,hipe_rtl:mk_imm(Key)),
583
 
             hipe_rtl:mk_branch(KeyReg, eq, Reg,
584
 
                                Label, 
585
 
                                hipe_rtl:label_name(Default) , 0.5)]
586
 
    end.
587
 
 
588
 
 
589
 
 
590
 
inline_atom_search(Start,End, Block, LBlock, KeyReg, Default, Labels) ->
591
 
        Reg = hipe_rtl:mk_new_reg(),
592
 
 
593
 
        Length = (End - Start) +1,
594
 
        
595
 
        if
596
 
          Length >= 3 ->
597
 
                Lab1 = hipe_rtl:mk_new_label(),
598
 
                Lab2 = hipe_rtl:mk_new_label(),
599
 
                Lab3 = hipe_rtl:mk_new_label(),
600
 
                Lab4 = hipe_rtl:mk_new_label(),
601
 
 
602
 
                Mid = ((End-Start) div 2)+Start,
603
 
                End1 = Mid-1,
604
 
                Start1 = Mid+1,
605
 
                A = [
606
 
                    hipe_rtl:mk_load_word_index(Reg,Block,Mid),
607
 
                    hipe_rtl:mk_branch(KeyReg, lt, Reg,
608
 
                                        hipe_rtl:label_name(Lab2),
609
 
                                        hipe_rtl:label_name(Lab1), 0.5),
610
 
                    Lab1,
611
 
                    hipe_rtl:mk_branch(KeyReg, gt, Reg,
612
 
                                        hipe_rtl:label_name(Lab3),
613
 
                                        hipe_rtl:label_name(Lab4), 0.5),
614
 
                    Lab4,
615
 
                    hipe_rtl:mk_goto_index(LBlock, Mid, Labels),
616
 
                    Lab2
617
 
                    ],
618
 
                B = [inline_atom_search(Start,End1,Block,LBlock,KeyReg,Default,Labels)],
619
 
                C = [inline_atom_search(Start1,End,Block,LBlock,KeyReg,Default,Labels)],                
620
 
                A ++ B ++ [Lab3] ++ C;
621
 
          
622
 
          Length == 2 ->
623
 
                L1 = hipe_rtl:mk_new_label(),
624
 
                L2 = hipe_rtl:mk_new_label(),
625
 
                L3 = hipe_rtl:mk_new_label(),
626
 
                [
627
 
                hipe_rtl:mk_load_word_index(Reg,Block,Start),
628
 
                hipe_rtl:mk_branch(KeyReg,eq,Reg,
629
 
                                        hipe_rtl:label_name(L1),
630
 
                                        hipe_rtl:label_name(L2), 0.5),
631
 
                L1,
632
 
                hipe_rtl:mk_goto_index(LBlock,Start,Labels),
633
 
                
634
 
                L2,
635
 
                hipe_rtl:mk_load_word_index(Reg,Block,End),
636
 
                hipe_rtl:mk_branch(KeyReg,eq,Reg,
637
 
                                        hipe_rtl:label_name(L3),
638
 
                                        hipe_rtl:label_name(Default), 0.5),
639
 
                L3,
640
 
                hipe_rtl:mk_goto_index(LBlock, End, Labels)
641
 
                ];
642
 
                
643
 
          Length == 1 ->
644
 
                NewLab = hipe_rtl:mk_new_label(),
645
 
                [
646
 
                hipe_rtl:mk_load_word_index(Reg,Block,Start),
647
 
                hipe_rtl:mk_branch(KeyReg, eq, Reg,
648
 
                                   hipe_rtl:label_name(NewLab),
649
 
                                   hipe_rtl:label_name(Default) , 0.9),
650
 
                NewLab,
651
 
                hipe_rtl:mk_goto_index(LBlock, Start, Labels)
652
 
                ]
653
 
        end.
 
502
  %% Create some registers and labels that we need.
 
503
  Reg = hipe_rtl:mk_new_reg_gcsafe(),
 
504
  Lab1 = hipe_rtl:mk_new_label(),
 
505
  Lab2 = hipe_rtl:mk_new_label(),
 
506
  Lab3 = hipe_rtl:mk_new_label(),
 
507
  
 
508
  Length = length(KeyList),
 
509
  
 
510
  if
 
511
    Length >= 3 ->
 
512
      %% Get middle element and keys/labels before that and after
 
513
      Middle_pos = get_middle(KeyList),
 
514
      Middle_key = lists:nth(Middle_pos, KeyList),
 
515
      Keys_beginning = get_cases(KeyList, 0, Middle_pos - 1),
 
516
      Labels_beginning = get_cases(LabelList, 0, Middle_pos - 1),
 
517
      Keys_ending = get_cases(KeyList, Middle_pos, Length),
 
518
      Labels_ending = get_cases(LabelList, Middle_pos, Length),
 
519
      
 
520
      %% Create the code.
 
521
      
 
522
      %% Get the label and build it up properly
 
523
      Middle_label = lists:nth(Middle_pos, LabelList),
 
524
      
 
525
      A = [hipe_rtl:mk_move(Reg, hipe_rtl:mk_imm(Middle_key)),
 
526
           hipe_rtl:mk_branch(KeyReg, lt, Reg, 
 
527
                              hipe_rtl:label_name(Lab2), 
 
528
                              hipe_rtl:label_name(Lab1), 0.5),
 
529
           Lab1,
 
530
           hipe_rtl:mk_branch(KeyReg, gt, Reg,
 
531
                              hipe_rtl:label_name(Lab3), 
 
532
                              Middle_label , 0.5),
 
533
           Lab2],
 
534
      %% build search tree for keys less than the middle element
 
535
      B = inline_search(Keys_beginning, Labels_beginning, KeyReg, Default),
 
536
      %% ...and for keys bigger than the middle element
 
537
      D = inline_search(Keys_ending, Labels_ending, KeyReg, Default),
 
538
      
 
539
      %% append the code and return it
 
540
      A ++ B ++ [Lab3] ++ D;
 
541
    
 
542
    Length =:= 2 ->
 
543
      %% get the first and second elements and theirs labels
 
544
      Key_first = hd(KeyList),
 
545
      First_label = hd(LabelList),
 
546
      
 
547
      %% Key_second = hipe_tagscheme:mk_fixnum(lists:nth(2, KeyList)),
 
548
      Key_second = lists:nth(2, KeyList),
 
549
      Second_label = lists:nth(2, LabelList),
 
550
      
 
551
      NewLab = hipe_rtl:mk_new_label(),
 
552
      
 
553
      %% compare them
 
554
      A = [hipe_rtl:mk_move(Reg,hipe_rtl:mk_imm(Key_first)),
 
555
           hipe_rtl:mk_branch(KeyReg, eq, Reg,
 
556
                              First_label, 
 
557
                              hipe_rtl:label_name(NewLab) , 0.5),
 
558
           NewLab],
 
559
      
 
560
      B = [hipe_rtl:mk_move(Reg,hipe_rtl:mk_imm(Key_second)),
 
561
           hipe_rtl:mk_branch(KeyReg, eq, Reg,
 
562
                              Second_label, 
 
563
                              hipe_rtl:label_name(Default) , 0.5)],
 
564
      A ++ B;
 
565
    
 
566
    Length =:= 1 ->
 
567
      Key = hd(KeyList),
 
568
      Label = hd(LabelList),
 
569
      
 
570
      [hipe_rtl:mk_move(Reg,hipe_rtl:mk_imm(Key)),
 
571
       hipe_rtl:mk_branch(KeyReg, eq, Reg,
 
572
                          Label, 
 
573
                          hipe_rtl:label_name(Default) , 0.5)]
 
574
  end.
 
575
 
 
576
 
 
577
inline_atom_search(Start, End, Block, LBlock, KeyReg, Default, Labels) ->
 
578
  Reg = hipe_rtl:mk_new_reg_gcsafe(),
 
579
  
 
580
  Length = (End - Start) +1,
 
581
  
 
582
  if
 
583
    Length >= 3 ->
 
584
      Lab1 = hipe_rtl:mk_new_label(),
 
585
      Lab2 = hipe_rtl:mk_new_label(),
 
586
      Lab3 = hipe_rtl:mk_new_label(),
 
587
      Lab4 = hipe_rtl:mk_new_label(),
 
588
      
 
589
      Mid = ((End-Start) div 2)+Start,
 
590
      End1 = Mid-1,
 
591
      Start1 = Mid+1,
 
592
      A = [
 
593
           hipe_rtl:mk_load_word_index(Reg,Block,Mid),
 
594
           hipe_rtl:mk_branch(KeyReg, lt, Reg,
 
595
                              hipe_rtl:label_name(Lab2),
 
596
                              hipe_rtl:label_name(Lab1), 0.5),
 
597
           Lab1,
 
598
           hipe_rtl:mk_branch(KeyReg, gt, Reg,
 
599
                              hipe_rtl:label_name(Lab3),
 
600
                              hipe_rtl:label_name(Lab4), 0.5),
 
601
           Lab4,
 
602
           hipe_rtl:mk_goto_index(LBlock, Mid, Labels),
 
603
           Lab2
 
604
          ],
 
605
      B = [inline_atom_search(Start,End1,Block,LBlock,KeyReg,Default,Labels)],
 
606
      C = [inline_atom_search(Start1,End,Block,LBlock,KeyReg,Default,Labels)],
 
607
      A ++ B ++ [Lab3] ++ C;
 
608
    
 
609
    Length =:= 2 ->
 
610
      L1 = hipe_rtl:mk_new_label(),
 
611
      L2 = hipe_rtl:mk_new_label(),
 
612
      L3 = hipe_rtl:mk_new_label(),
 
613
      [
 
614
       hipe_rtl:mk_load_word_index(Reg,Block,Start),
 
615
       hipe_rtl:mk_branch(KeyReg,eq,Reg,
 
616
                          hipe_rtl:label_name(L1),
 
617
                          hipe_rtl:label_name(L2), 0.5),
 
618
       L1,
 
619
       hipe_rtl:mk_goto_index(LBlock,Start,Labels),
 
620
       
 
621
       L2,
 
622
       hipe_rtl:mk_load_word_index(Reg,Block,End),
 
623
       hipe_rtl:mk_branch(KeyReg,eq,Reg,
 
624
                          hipe_rtl:label_name(L3),
 
625
                          hipe_rtl:label_name(Default), 0.5),
 
626
       L3,
 
627
       hipe_rtl:mk_goto_index(LBlock, End, Labels)
 
628
      ];
 
629
    
 
630
    Length =:= 1 ->
 
631
      NewLab = hipe_rtl:mk_new_label(),
 
632
      [
 
633
       hipe_rtl:mk_load_word_index(Reg,Block,Start),
 
634
       hipe_rtl:mk_branch(KeyReg, eq, Reg,
 
635
                          hipe_rtl:label_name(NewLab),
 
636
                          hipe_rtl:label_name(Default), 0.9),
 
637
       NewLab,
 
638
       hipe_rtl:mk_goto_index(LBlock, Start, Labels)
 
639
      ]
 
640
  end.
654
641
 
655
642
 
656
643
%% Create a jumptable
657
644
gen_jump_table(Arg,Fail,IcodeFail,VarMap,ConstTab,Cases,Min) ->
658
 
          %% Map is a rtl mapping of Dense
659
 
          {Max,DenseTbl} = dense_interval(Cases,Min,IcodeFail),
660
 
          {Map,VarMap2} = lbls_from_cases(DenseTbl,VarMap),
661
 
 
662
 
          %% Make some labels and registers that we need.
663
 
          BelowLab = hipe_rtl:mk_new_label(),
664
 
          UntaggedR = hipe_rtl:mk_new_reg(),
665
 
          StartR = hipe_rtl:mk_new_reg(),
666
 
 
667
 
          %% Generate the code to do the switch...
668
 
          {[
669
 
            %% Untag the index.
670
 
            %% 
671
 
            %% OBS:
672
 
            %% TODO: Use the tagscheme module for this!
673
 
            hipe_rtl:mk_alu(UntaggedR, Arg, sra, hipe_rtl:mk_imm(4))|
674
 
            %% Check that the index is within Min and Max.
675
 
            case Min of
676
 
              0 -> %% First element is 0 this is simple.
677
 
                [hipe_rtl:mk_branch(UntaggedR, gtu, hipe_rtl:mk_imm(Max),
678
 
                                     hipe_rtl:label_name(Fail), 
679
 
                                     hipe_rtl:label_name(BelowLab) , 0.01),
680
 
                 BelowLab,
681
 
                 %% StartR contains the index into the jumptable
682
 
                 hipe_rtl:mk_switch(UntaggedR, Map)];
683
 
              _ -> %% First element is not 0 
684
 
                [hipe_rtl:mk_alu(StartR, UntaggedR, sub, 
685
 
                                 hipe_rtl:mk_imm(Min)), 
686
 
                 hipe_rtl:mk_branch(StartR, gtu, hipe_rtl:mk_imm(Max-Min),
687
 
                                    hipe_rtl:label_name(Fail), 
688
 
                                    hipe_rtl:label_name(BelowLab) , 0.01),
689
 
                 BelowLab,
690
 
                 %% StartR contains the index into the jumptable
691
 
                 hipe_rtl:mk_switch(StartR, Map)]
692
 
            end],
693
 
            VarMap2,
694
 
            ConstTab}.
695
 
 
696
 
 
697
 
% Generate the jumptable for Cases while filling in unused positions
698
 
% with the fail label
 
645
  %% Map is a rtl mapping of Dense
 
646
  {Max,DenseTbl} = dense_interval(Cases,Min,IcodeFail),
 
647
  {Map,VarMap2} = lbls_from_cases(DenseTbl,VarMap),
 
648
  
 
649
  %% Make some labels and registers that we need.
 
650
  BelowLab = hipe_rtl:mk_new_label(),
 
651
  UntaggedR = hipe_rtl:mk_new_reg_gcsafe(),
 
652
  StartR = hipe_rtl:mk_new_reg_gcsafe(),
 
653
  
 
654
  %% Generate the code to do the switch...
 
655
  {[
 
656
    %% Untag the index.
 
657
    hipe_tagscheme:untag_fixnum(UntaggedR, Arg)|
 
658
    %% Check that the index is within Min and Max.
 
659
    case Min of
 
660
      0 -> %% First element is 0 this is simple.
 
661
        [hipe_rtl:mk_branch(UntaggedR, gtu, hipe_rtl:mk_imm(Max),
 
662
                            hipe_rtl:label_name(Fail), 
 
663
                            hipe_rtl:label_name(BelowLab), 0.01),
 
664
         BelowLab,
 
665
         %% StartR contains the index into the jumptable
 
666
         hipe_rtl:mk_switch(UntaggedR, Map)];
 
667
      _ -> %% First element is not 0 
 
668
        [hipe_rtl:mk_alu(StartR, UntaggedR, sub, 
 
669
                         hipe_rtl:mk_imm(Min)), 
 
670
         hipe_rtl:mk_branch(StartR, gtu, hipe_rtl:mk_imm(Max-Min),
 
671
                            hipe_rtl:label_name(Fail), 
 
672
                            hipe_rtl:label_name(BelowLab), 0.01),
 
673
         BelowLab,
 
674
         %% StartR contains the index into the jumptable
 
675
         hipe_rtl:mk_switch(StartR, Map)]
 
676
    end],
 
677
   VarMap2,
 
678
   ConstTab}.
 
679
 
 
680
 
 
681
%% Generate the jumptable for Cases while filling in unused positions
 
682
%% with the fail label
699
683
 
700
684
dense_interval(Cases, Min, IcodeFail) ->
701
 
        dense_interval(Cases, Min, IcodeFail, 0, 0).
 
685
  dense_interval(Cases, Min, IcodeFail, 0, 0).
702
686
dense_interval([Pair = {Const,_}|Rest], Pos, Fail, Range, NoEntries) ->
703
 
        Val= hipe_icode:const_value(Const),
704
 
        if 
705
 
            Pos < Val ->
706
 
                {Max, Res} = 
707
 
                dense_interval([Pair|Rest], Pos+1, Fail, Range+1, NoEntries),
708
 
                {Max,[{hipe_icode:mk_const(Pos), Fail}|Res]};
709
 
            true ->
710
 
                {Max, Res} = dense_interval(Rest, Pos+1, Fail, Range+1, NoEntries+1),
711
 
                {Max, [Pair | Res]}
712
 
        end;
 
687
  Val = hipe_icode:const_value(Const),
 
688
  if 
 
689
    Pos < Val ->
 
690
      {Max, Res} = 
 
691
        dense_interval([Pair|Rest], Pos+1, Fail, Range+1, NoEntries),
 
692
      {Max,[{hipe_icode:mk_const(Pos), Fail}|Res]};
 
693
    true ->
 
694
      {Max, Res} = dense_interval(Rest, Pos+1, Fail, Range+1, NoEntries+1),
 
695
      {Max, [Pair | Res]}
 
696
  end;
713
697
dense_interval([], Max, _, _, _) -> 
714
 
        {Max-1, []}.
 
698
  {Max-1, []}.
715
699
 
716
700
 
717
701
%%-------------------------------------------------------------------------
718
702
%% switch_val without jumptable
719
703
%%
720
704
 
721
 
gen_slow_switch_val(I, VarMap, ConstTab, Options, ExitInfo) ->
 
705
gen_slow_switch_val(I, VarMap, ConstTab, Options) ->
722
706
  Is = rewrite_switch_val(I),
723
707
  ?IF_DEBUG_LEVEL(3,?msg("Switch: ~w\n",[Is]),no_debug),
724
 
  hipe_icode2rtl:translate_instrs(Is, VarMap, ConstTab, Options, ExitInfo).
 
708
  hipe_icode2rtl:translate_instrs(Is, VarMap, ConstTab, Options).
725
709
 
726
710
rewrite_switch_val(I) ->
727
 
    Arg = hipe_icode:switch_val_arg(I),
728
 
    Fail = hipe_icode:switch_val_fail_label(I),
729
 
    Cases = hipe_icode:switch_val_cases(I),
730
 
    rewrite_switch_val_cases(Cases, Fail, Arg).
 
711
  Arg = hipe_icode:switch_val_arg(I),
 
712
  Fail = hipe_icode:switch_val_fail_label(I),
 
713
  Cases = hipe_icode:switch_val_cases(I),
 
714
  rewrite_switch_val_cases(Cases, Fail, Arg).
731
715
 
732
716
rewrite_switch_val_cases([{C,L}|Cases], Fail, Arg) ->
733
 
    Tmp = hipe_icode:mk_new_var(),
734
 
    NextLab = hipe_icode:mk_new_label(),
735
 
    [hipe_icode:mk_mov(Tmp, C),
736
 
     hipe_icode:mk_if(op_exact_eqeq_2, [Arg, Tmp], L,
737
 
                      hipe_icode:label_name(NextLab)),
738
 
     NextLab |
739
 
     rewrite_switch_val_cases(Cases, Fail, Arg)];
 
717
  Tmp = hipe_icode:mk_new_var(),
 
718
  NextLab = hipe_icode:mk_new_label(),
 
719
  [hipe_icode:mk_move(Tmp, C),
 
720
   hipe_icode:mk_if(op_exact_eqeq_2, [Arg, Tmp], L,
 
721
                    hipe_icode:label_name(NextLab)),
 
722
   NextLab |
 
723
   rewrite_switch_val_cases(Cases, Fail, Arg)];
740
724
rewrite_switch_val_cases([], Fail, _Arg) ->
741
 
    [hipe_icode:mk_goto(Fail)].
 
725
  [hipe_icode:mk_goto(Fail)].
742
726
 
743
727
 
744
728
%%-------------------------------------------------------------------------
746
730
%%
747
731
 
748
732
gen_search_switch_val(Arg, Cases, Default, VarMap, ConstTab, _Options) ->
749
 
  ValTableR = hipe_rtl:mk_new_reg(),
 
733
  ValTableR = hipe_rtl:mk_new_reg_gcsafe(),
750
734
 
751
735
  {Values,_Labels} = split_cases(Cases),
752
 
  {NewConstTab,Id} =
753
 
       hipe_consttab:insert_sorted_block(ConstTab, 
754
 
                              Values),
 
736
  {NewConstTab,Id} = hipe_consttab:insert_sorted_block(ConstTab, Values),
755
737
  {LabMap,VarMap1} = lbls_from_cases(Cases,VarMap),
756
738
  
757
739
  Code = 
762
744
 
763
745
%%-------------------------------------------------------------------------
764
746
%%
765
 
%% tab/5 creates rtl code for a binary search.
 
747
%% tab/5 creates RTL code for a binary search.
766
748
%% It requires two sorted tables one with the keys to search
767
749
%% through and one with the corresponding labels to jump to.
768
750
%%
867
849
  LastOffset = (length(KeyList)-1)*?WORDSIZE, 
868
850
 
869
851
  %% Calculate the power of two closest to the size of the table.
870
 
  Pow2 = 
871
 
    trunc(math:pow(2,(trunc(math:log(LastOffset) / math:log(2))))),
 
852
  Pow2 = trunc(math:pow(2,(trunc(math:log(LastOffset) / math:log(2))))),
872
853
 
873
854
  %% Create some registers an lables that we need.
874
 
  IndexReg = hipe_rtl:mk_new_reg(),
875
 
  Temp = hipe_rtl:mk_new_reg(),
876
 
  Temp2 = hipe_rtl:mk_new_reg(),
 
855
  IndexReg = hipe_rtl:mk_new_reg_gcsafe(),
 
856
  Temp = hipe_rtl:mk_new_reg_gcsafe(),
 
857
  Temp2 = hipe_rtl:mk_new_reg_gcsafe(),
877
858
  Lab1 = hipe_rtl:mk_new_label(),
878
859
  Lab2 = hipe_rtl:mk_new_label(),
879
860
  Lab3 = hipe_rtl:mk_new_label(),
888
869
   hipe_rtl:mk_load(Temp,TablePntrReg,hipe_rtl:mk_imm(Init)),
889
870
   hipe_rtl:mk_branch(Temp, ge, KeyReg,
890
871
                      hipe_rtl:label_name(Lab2), 
891
 
                      hipe_rtl:label_name(Lab1) , 0.5),
 
872
                      hipe_rtl:label_name(Lab1), 0.5),
892
873
   Lab1,
893
874
   hipe_rtl:mk_alu(IndexReg, IndexReg, add, 
894
875
                   hipe_rtl:mk_imm(Init+?WORDSIZE)),
899
880
 
900
881
    [hipe_rtl:mk_branch(IndexReg, gt, hipe_rtl:mk_imm(LastOffset),
901
882
                       hipe_rtl:label_name(Default), 
902
 
                       hipe_rtl:label_name(Lab3) , 0.5),
 
883
                       hipe_rtl:label_name(Lab3), 0.5),
903
884
     Lab3,
904
885
     hipe_rtl:mk_load(Temp2,TablePntrReg,IndexReg),
905
886
     hipe_rtl:mk_branch(Temp2, eq, KeyReg,
906
887
                        hipe_rtl:label_name(Lab4), 
907
 
                        hipe_rtl:label_name(Default) , 0.9),
 
888
                        hipe_rtl:label_name(Default), 0.9),
908
889
     Lab4,
909
 
     hipe_rtl:mk_alu(IndexReg, IndexReg, sra, 
910
 
                   hipe_rtl:mk_imm(2)),
911
 
     hipe_rtl:mk_sorted_switch(IndexReg, LabelList, KeyList)]
912
 
    .
913
 
 
914
 
step(?WORDSIZE,TablePntrReg,IndexReg,KeyReg) ->
915
 
  Temp = hipe_rtl:mk_new_reg(),
916
 
  TempIndex = hipe_rtl:mk_new_reg(),
917
 
  Lab1 = hipe_rtl:mk_new_label(),
918
 
  Lab2 = hipe_rtl:mk_new_label(),
919
 
 
920
 
  [hipe_rtl:mk_alu(TempIndex, IndexReg, add, 
921
 
                   hipe_rtl:mk_imm(?WORDSIZE)),
922
 
 
923
 
   hipe_rtl:mk_load(Temp,TablePntrReg,TempIndex),
924
 
   hipe_rtl:mk_branch(Temp, gt, KeyReg,
925
 
                      hipe_rtl:label_name(Lab2), 
926
 
                      hipe_rtl:label_name(Lab1) , 0.5),
927
 
   Lab1,
928
 
   hipe_rtl:mk_alu(IndexReg, IndexReg, add, 
929
 
                   hipe_rtl:mk_imm(?WORDSIZE)),
930
 
   hipe_rtl:mk_goto(hipe_rtl:label_name(Lab2)),
931
 
   Lab2
932
 
  ];
 
890
     hipe_rtl:mk_alu(IndexReg, IndexReg, sra,
 
891
                     hipe_rtl:mk_imm(hipe_rtl_arch:log2_word_size())),
 
892
     hipe_rtl:mk_sorted_switch(IndexReg, LabelList, KeyList)
 
893
    ].
 
894
 
933
895
step(I,TablePntrReg,IndexReg,KeyReg) ->
934
 
  Temp = hipe_rtl:mk_new_reg(),
935
 
  TempIndex = hipe_rtl:mk_new_reg(),
 
896
  Temp = hipe_rtl:mk_new_reg_gcsafe(),
 
897
  TempIndex = hipe_rtl:mk_new_reg_gcsafe(),
936
898
  Lab1 = hipe_rtl:mk_new_label(),
937
899
  Lab2 = hipe_rtl:mk_new_label(),
938
 
 
939
900
  [hipe_rtl:mk_alu(TempIndex, IndexReg, add, hipe_rtl:mk_imm(I)),
940
901
   hipe_rtl:mk_load(Temp,TablePntrReg,TempIndex),
941
902
   hipe_rtl:mk_branch(Temp, gt, KeyReg,
942
 
                      hipe_rtl:label_name(Lab2), 
943
 
                      hipe_rtl:label_name(Lab1) , 0.5),
944
 
   Lab1,
945
 
   hipe_rtl:mk_move(IndexReg, TempIndex),
946
 
   hipe_rtl:mk_goto(hipe_rtl:label_name(Lab2)),
947
 
   Lab2 |
948
 
   step(I div 2,TablePntrReg,IndexReg,KeyReg)].
949
 
 
950
 
 
 
903
                      hipe_rtl:label_name(Lab2), 
 
904
                      hipe_rtl:label_name(Lab1) , 0.5),
 
905
   Lab1] ++
 
906
    case ?WORDSIZE of
 
907
      I -> %% Recursive base case
 
908
        [hipe_rtl:mk_alu(IndexReg, IndexReg, add, hipe_rtl:mk_imm(I)),
 
909
         hipe_rtl:mk_goto(hipe_rtl:label_name(Lab2)),
 
910
         Lab2
 
911
        ];
 
912
      _ -> %% Recursion case
 
913
        [hipe_rtl:mk_move(IndexReg, TempIndex),
 
914
         hipe_rtl:mk_goto(hipe_rtl:label_name(Lab2)),
 
915
         Lab2
 
916
         | step(I div 2,TablePntrReg,IndexReg,KeyReg)
 
917
        ]
 
918
    end.
951
919
 
952
920
%%-------------------------------------------------------------------------
953
921
 
968
936
 
969
937
%%-------------------------------------------------------------------------
970
938
%%
971
 
%%
972
 
%%-------------------------------------------------------------------------
973
 
 
974
 
%%
975
939
%% {switch_tuple_arity,X,Fail,N,[{A1,L1},...,{AN,LN}]}
976
940
%%
977
941
%% if not boxed(X) goto Fail
979
943
%% switch_int(Hdr,Fail,[{H(A1),L1},...,{H(AN),LN}])
980
944
%% where H(Ai) = make_arityval(Ai)
981
945
%% 
 
946
%%-------------------------------------------------------------------------
982
947
 
983
 
gen_switch_tuple(I, Map, ConstTab, _Options, _ExitInfo) ->
984
 
    {X, Map1} = 
 
948
gen_switch_tuple(I, Map, ConstTab, _Options) ->
 
949
  {X, Map1} = 
985
950
    hipe_rtl_varmap:icode_var2rtl_var(hipe_icode:switch_tuple_arity_arg(I), Map),
986
 
    Fail0 = hipe_icode:switch_tuple_arity_fail_label(I),
987
 
    {Fail1, Map2} = 
988
 
    hipe_rtl_varmap:icode_label2rtl_label(Fail0, Map1),
989
 
    FailLab = hipe_rtl:label_name(Fail1),
990
 
    {Cases, Map3} =
991
 
        lists:foldr(fun({A,L}, {Rest,M}) ->
992
 
                            {L1,M1} = hipe_rtl_varmap:icode_label2rtl_label(L, M),
993
 
                            L2 = hipe_rtl:label_name(L1),
994
 
                            A1 = hipe_icode:const_value(A),
995
 
                            H1 = hipe_tagscheme:mk_arityval(A1),
996
 
                            {[{H1,L2}|Rest], M1} end,
997
 
                    {[], Map2},
998
 
                    hipe_icode:switch_tuple_arity_cases(I)),
999
 
    Hdr = hipe_rtl:mk_new_reg(),
1000
 
    IsBoxedLab = hipe_rtl:mk_new_label(),
1001
 
    {[hipe_tagscheme:test_is_boxed(X, hipe_rtl:label_name(IsBoxedLab),
1002
 
                                   FailLab, 0.9),
1003
 
      IsBoxedLab,
1004
 
      hipe_tagscheme:get_header(Hdr, X) |
1005
 
      gen_switch_int(Hdr, FailLab, Cases)],
1006
 
     Map3, ConstTab}.
 
951
  Fail0 = hipe_icode:switch_tuple_arity_fail_label(I),
 
952
  {Fail1, Map2} =  hipe_rtl_varmap:icode_label2rtl_label(Fail0, Map1),
 
953
  FailLab = hipe_rtl:label_name(Fail1),
 
954
  {Cases, Map3} =
 
955
    lists:foldr(fun({A,L}, {Rest,M}) ->
 
956
                    {L1,M1} = hipe_rtl_varmap:icode_label2rtl_label(L, M),
 
957
                    L2 = hipe_rtl:label_name(L1),
 
958
                    A1 = hipe_icode:const_value(A),
 
959
                    H1 = hipe_tagscheme:mk_arityval(A1),
 
960
                    {[{H1,L2}|Rest], M1} end,
 
961
                {[], Map2},
 
962
                hipe_icode:switch_tuple_arity_cases(I)),
 
963
  Hdr = hipe_rtl:mk_new_reg_gcsafe(),
 
964
  IsBoxedLab = hipe_rtl:mk_new_label(),
 
965
  {[hipe_tagscheme:test_is_boxed(X, hipe_rtl:label_name(IsBoxedLab),
 
966
                                 FailLab, 0.9),
 
967
    IsBoxedLab,
 
968
    hipe_tagscheme:get_header(Hdr, X) |
 
969
    gen_switch_int(Hdr, FailLab, Cases)],
 
970
   Map3, ConstTab}.
1007
971
 
1008
972
%%
1009
 
%% rtl-level switch-on-int
 
973
%% RTL-level switch-on-int
1010
974
%%
1011
975
 
1012
976
gen_switch_int(X, FailLab, [{C,L}|Rest]) ->
1013
 
    NextLab = hipe_rtl:mk_new_label(),
1014
 
    [hipe_rtl:mk_branch(X, eq, hipe_rtl:mk_imm(C), L,
1015
 
                        hipe_rtl:label_name(NextLab), 0.5),
1016
 
     NextLab |
1017
 
     gen_switch_int(X, FailLab, Rest)];
 
977
  NextLab = hipe_rtl:mk_new_label(),
 
978
  [hipe_rtl:mk_branch(X, eq, hipe_rtl:mk_imm(C), L,
 
979
                      hipe_rtl:label_name(NextLab), 0.5),
 
980
   NextLab |
 
981
   gen_switch_int(X, FailLab, Rest)];
1018
982
gen_switch_int(_, FailLab, []) ->
1019
 
    [hipe_rtl:mk_goto(FailLab)].
 
983
  [hipe_rtl:mk_goto(FailLab)].