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

« back to all changes in this revision

Viewing changes to lib/hipe/arm/hipe_arm_cfg.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$
 
3
 
 
4
-module(hipe_arm_cfg).
 
5
 
 
6
-export([init/1,
 
7
         labels/1, start_label/1,
 
8
         succ/2, succ_map/1,
 
9
         bb/2, bb_add/3]).
 
10
-export([postorder/1]).
 
11
-export([linearise/1]).
 
12
-export([params/1, reverse_postorder/1]).
 
13
-export([arity/1]). % for linear scan
 
14
%%-export([redirect_jmp/3]).
 
15
 
 
16
%%% these tell cfg.inc what to define (ugly as hell)
 
17
-define(BREADTH_ORDER,true). % for linear scan
 
18
-define(PARAMS_NEEDED,true).
 
19
-define(START_LABEL_UPDATE_NEEDED,true).
 
20
-include("../flow/cfg.inc").
 
21
-include("hipe_arm.hrl").
 
22
 
 
23
init(Defun) ->
 
24
  Code = hipe_arm:defun_code(Defun),
 
25
  StartLab = hipe_arm:label_label(hd(Code)),
 
26
  Data = hipe_arm:defun_data(Defun),
 
27
  IsClosure = hipe_arm:defun_is_closure(Defun),
 
28
  Name = hipe_arm:defun_mfa(Defun),
 
29
  IsLeaf = hipe_arm:defun_is_leaf(Defun),
 
30
  Formals = hipe_arm:defun_formals(Defun),
 
31
  Extra = [],
 
32
  CFG0 = mk_empty_cfg(Name, StartLab, Data,
 
33
                      IsClosure, IsLeaf, Formals, Extra),
 
34
  take_bbs(Code, CFG0).
 
35
 
 
36
is_branch(I) ->
 
37
  case I of
 
38
    #b_fun{} -> true;
 
39
    #b_label{'cond'='al'} -> true;
 
40
    #pseudo_bc{} -> true;
 
41
    #pseudo_blr{} -> true;
 
42
    #pseudo_bx{} -> true;
 
43
    #pseudo_call{} -> true;
 
44
    #pseudo_switch{} -> true;
 
45
    #pseudo_tailcall{} -> true;
 
46
    _ -> false
 
47
  end.
 
48
 
 
49
branch_successors(Branch) ->
 
50
  case Branch of
 
51
    #b_fun{} -> [];
 
52
    #b_label{'cond'='al',label=Label} -> [Label];
 
53
    #pseudo_bc{true_label=TrueLab,false_label=FalseLab} -> [FalseLab,TrueLab];
 
54
    #pseudo_blr{} -> [];
 
55
    #pseudo_bx{} -> [];
 
56
    #pseudo_call{contlab=ContLab, sdesc=#arm_sdesc{exnlab=ExnLab}} ->
 
57
      case ExnLab of
 
58
        [] -> [ContLab];
 
59
        _ -> [ContLab,ExnLab]
 
60
      end;
 
61
    #pseudo_switch{labels=Labels} -> Labels;
 
62
    #pseudo_tailcall{} -> []
 
63
  end.
 
64
 
 
65
-ifdef(REMOVE_TRIVIAL_BBS_NEEDED).
 
66
fails_to(_Instr) -> [].
 
67
-endif.
 
68
 
 
69
-ifdef(notdef).
 
70
redirect_jmp(I, Old, New) ->
 
71
  case I of
 
72
    #b_label{label=Label} ->
 
73
      if Old =:= Label -> I#b_label{label=New};
 
74
         true -> I
 
75
      end;
 
76
    #pseudo_bc{true_label=TrueLab, false_label=FalseLab} ->
 
77
      I1 = if Old =:= TrueLab -> I#pseudo_bc{true_label=New};
 
78
              true -> I
 
79
           end,
 
80
      if Old =:= FalseLab -> I1#pseudo_bc{false_label=New};
 
81
         true -> I1
 
82
      end;
 
83
    %% handle pseudo_call too?
 
84
    _ -> I
 
85
  end.
 
86
-endif.
 
87
 
 
88
mk_goto(Label) ->
 
89
  hipe_arm:mk_b_label(Label).
 
90
 
 
91
is_label(I) ->
 
92
  hipe_arm:is_label(I).
 
93
 
 
94
label_name(Label) ->
 
95
  hipe_arm:label_label(Label).
 
96
 
 
97
mk_label(Name) ->
 
98
  hipe_arm:mk_label(Name).
 
99
 
 
100
linearise(CFG) ->       % -> defun, not insn list
 
101
  Fun = function(CFG),
 
102
  Formals = params(CFG),
 
103
  Code = linearize_cfg(CFG),
 
104
  Data = data(CFG),
 
105
  VarRange = hipe_gensym:var_range(arm),
 
106
  LabelRange = hipe_gensym:label_range(arm),
 
107
  IsClosure = is_closure(CFG),
 
108
  IsLeaf = is_leaf(CFG),
 
109
  hipe_arm:mk_defun(Fun, Formals, IsClosure, IsLeaf,
 
110
                    Code, Data, VarRange, LabelRange).
 
111
 
 
112
arity(CFG) ->
 
113
  #arm_mfa{a=Arity} = function(CFG),
 
114
  Arity.