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

« back to all changes in this revision

Viewing changes to lib/hipe/icode/hipe_icode_heap_test.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 -*-
1
2
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2
3
%% Copyright (c) 2000 by Erik Johansson.  All Rights Reserved 
3
 
%% Time-stamp: <02/05/13 14:57:10 happi>
4
4
%% ====================================================================
5
5
%%  Filename :  hipe_icode_heap_test.erl
6
6
%%  Module   :  hipe_icode_heap_test
8
8
%%  Notes    : 
9
9
%%  History  :  * 2000-11-07 Erik Johansson (happi@csd.uu.se): 
10
10
%%               Created.
11
 
%%  CVS      :
12
 
%%              $Author: tobiasl $
13
 
%%              $Date: 2003/03/21 16:21:28 $
14
 
%%              $Revision: 1.9 $
15
 
%% ====================================================================
16
 
%%  Exports  :
17
 
%%
18
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
11
%%
 
12
%% $Id$
 
13
%%
19
14
 
20
15
-module(hipe_icode_heap_test).
 
16
 
21
17
-export([cfg/1]).
22
18
 
23
19
%-ifndef(DEBUG).
24
20
%-define(DEBUG,1).
25
21
%-endif.
26
22
-define(DO_ASSERT,true).
 
23
 
27
24
-include("../main/hipe.hrl").
 
25
-include("hipe_icode.hrl").
 
26
 
28
27
%-------------------------------------------------------------------------
29
28
-include("../rtl/hipe_literals.hrl").
30
29
%-------------------------------------------------------------------------
31
30
 
32
31
 
33
32
cfg(CFG) ->
34
 
  Icode = hipe_icode_cfg:linearize(CFG),
35
 
  CFG2 = hipe_icode_cfg:init(Icode),
36
 
 
 
33
  Icode = hipe_icode_cfg:cfg_to_linear(CFG),
37
34
  Code = hipe_icode:icode_code(Icode),
38
35
  ActualVmax = hipe_icode:highest_var(Code),
39
36
  ActualLmax = hipe_icode:highest_label(Code),
41
38
  hipe_gensym:set_label(icode,ActualLmax+1),
42
39
  hipe_gensym:set_var(icode,ActualVmax+1),
43
40
 
44
 
  EBBs = hipe_icode_ebb:cfg(CFG2),
45
 
  {EBBcode,_Visited} = ebbs(EBBs,[], CFG2),
 
41
  EBBs = hipe_icode_ebb:cfg(CFG),
 
42
  {EBBcode,_Visited} = ebbs(EBBs,[], CFG),
46
43
  NewCode = add_gc_tests(EBBcode),
47
44
  NewIcode = hipe_icode:icode_code_update(Icode,NewCode),
48
 
  
49
 
  NewCFG = hipe_icode_cfg:init(NewIcode),
 
45
 
 
46
  NewCFG = hipe_icode_cfg:linear_to_cfg(NewIcode),
50
47
  %% hipe_icode_cfg:pp(NewCFG),
51
48
  NewCFG.
52
49
 
102
99
need([I|Is] , Need, Code) ->
103
100
  case split(I) of 
104
101
    true -> 
105
 
      case hipe_icode:type(I) of
106
 
        call ->
 
102
      case I of
 
103
        #call{} ->
107
104
          case hipe_icode:call_continuation(I) of
108
105
            [] -> %% Was fallthrough.
109
106
              NewLab = hipe_icode:mk_new_label(),
123
120
  {Need, [], lists:reverse(Code)}.
124
121
 
125
122
need(I) ->
126
 
  case hipe_icode:type(I) of 
127
 
    call ->
128
 
      primop_need(I);
 
123
  case I of 
 
124
    #call{} ->
 
125
      primop_need(hipe_icode:call_fun(I), hipe_icode:call_args(I));
 
126
    #enter{} ->
 
127
      primop_need(hipe_icode:enter_fun(I), hipe_icode:enter_args(I));
129
128
    _ -> 
130
129
      0
131
130
  end.
132
131
              
133
 
primop_need(I) ->
134
 
  case hipe_icode:call_fun(I) of
135
 
 
 
132
primop_need(Op, As) ->
 
133
  case Op of
136
134
    cons ->
137
135
      2;
138
136
    mktuple ->
139
 
      length(hipe_icode:call_args(I)) + 1;
 
137
      length(As) + 1;
140
138
    {mkfun,_MFA,_MagicNum,_Index} ->
141
 
      NumFree = length(hipe_icode:call_args(I)),
 
139
      NumFree = length(As),
142
140
      ?ERL_FUN_SIZE + NumFree;
143
141
    unsafe_tag_float ->
144
142
      3;
154
152
   L].
155
153
 
156
154
split(I) ->
157
 
  case hipe_icode:type(I) of
158
 
    call -> split_primop(hipe_icode:call_fun(I));
159
 
    enter -> split_primop(hipe_icode:enter_fun(I));
160
 
    _ -> false
161
 
  end.
162
 
 
163
 
split_primop(Primop) ->
164
 
  not hipe_bif:known_heap_need(Primop).
165
 
 
 
155
  case I of
 
156
    #call{} -> not known_heap_need(hipe_icode:call_fun(I));
 
157
    #enter{} -> not known_heap_need(hipe_icode:enter_fun(I));
 
158
    _ -> false
 
159
  end.
 
160
 
 
161
known_heap_need(Name) ->
 
162
  case Name of
 
163
    %% Primops
 
164
    cons -> true;
 
165
    fcheckerror -> true;
 
166
    fclearerror -> true;
 
167
    fnegate -> true;
 
168
    fp_add -> true;
 
169
    fp_div -> true;
 
170
    fp_mul -> true;
 
171
    fp_sub -> true;
 
172
    mktuple -> true;
 
173
    unsafe_hd -> true;
 
174
    unsafe_tag_float -> true;
 
175
    unsafe_tl -> true;
 
176
    unsafe_untag_float -> true;
 
177
    {element, _TypeInfo} -> true;
 
178
    {unsafe_element,_N} -> true;
 
179
    {unsafe_update_element,_N}  -> true;
 
180
 
 
181
    %% MFAs
 
182
    {erlang, element, 2} -> true;
 
183
    {erlang, length, 1} -> true;
 
184
    {erlang, self, 0} -> true;
 
185
    {erlang, size, 1} -> true;
 
186
 
 
187
    _ -> false
 
188
  end.