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

« back to all changes in this revision

Viewing changes to lib/hipe/icode/hipe_icode_cfg.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
30
30
 
31
31
%%----------------------------------------------------------------------
32
32
 
33
 
-type(io_device() :: any()).    % XXX: DOES NOT BELONG HERE
 
33
-type io_device() :: any().    % XXX: DOES NOT BELONG HERE
34
34
 
35
35
%%----------------------------------------------------------------------
36
36
%% Prototypes for exported functions which are Icode specific
37
37
%%----------------------------------------------------------------------
38
38
 
39
 
-spec(labels/1            :: (#cfg{}) -> [icode_lbl()]).
40
 
-spec(postorder/1         :: (#cfg{}) -> [icode_lbl()]).
41
 
-spec(reverse_postorder/1 :: (#cfg{}) -> [icode_lbl()]).
42
 
 
43
 
-spec(is_visited/2 :: (icode_lbl(), gb_tree()) -> bool()).
44
 
-spec(visit/2      :: (icode_lbl(), gb_tree()) -> gb_tree()).
45
 
 
46
 
-spec(bb/2       :: (#cfg{}, icode_lbl()) -> 'not_found' | bb()).
47
 
-spec(bb_add/3   :: (#cfg{}, icode_lbl(), bb()) -> #cfg{}).
48
 
-spec(pred/2     :: (#cfg{}, icode_lbl()) -> [icode_lbl()]).
49
 
-spec(succ/2     :: (#cfg{}, icode_lbl()) -> [icode_lbl()]).
50
 
-spec(redirect/4 :: (#cfg{}, icode_lbl(), icode_lbl(), icode_lbl()) -> #cfg{}).
 
39
-spec labels(#cfg{}) -> [icode_lbl()].
 
40
-spec postorder(#cfg{}) -> [icode_lbl()].
 
41
-spec reverse_postorder(#cfg{}) -> [icode_lbl()].
 
42
 
 
43
-spec is_visited(icode_lbl(), gb_tree()) -> bool().
 
44
-spec visit(icode_lbl(), gb_tree()) -> gb_tree().
 
45
 
 
46
-spec bb(#cfg{}, icode_lbl()) -> 'not_found' | bb().
 
47
-spec bb_add(#cfg{}, icode_lbl(), bb()) -> #cfg{}.
 
48
-spec pred(#cfg{}, icode_lbl()) -> [icode_lbl()].
 
49
-spec succ(#cfg{}, icode_lbl()) -> [icode_lbl()].
 
50
-spec redirect(#cfg{}, icode_lbl(), icode_lbl(), icode_lbl()) -> #cfg{}.
51
51
 
52
52
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
53
53
%%
54
54
%% Interface to Icode
55
55
%%
56
56
 
57
 
-spec(linear_to_cfg/1 :: (#icode{}) -> #cfg{}).
 
57
-spec linear_to_cfg(#icode{}) -> #cfg{}.
 
58
 
58
59
linear_to_cfg(LinearIcode) ->
59
60
  %% hipe_icode_pp:pp(Icode),
60
61
  Code = hipe_icode:icode_code(LinearIcode),
84
85
%% remove_blocks(CFG, [Lbl|Lbls]) ->
85
86
%%   remove_blocks(bb_remove(CFG, Lbl), Lbls).
86
87
 
87
 
-spec(is_label/1 :: (icode_instr()) -> bool()).
 
88
-spec is_label(icode_instr()) -> bool().
88
89
is_label(Instr) ->
89
90
  hipe_icode:is_label(Instr).
90
91
 
104
105
  hipe_icode:fails_to(Instr).
105
106
 
106
107
%% True if instr has no effect.
107
 
-spec(is_comment/1 :: (icode_instr()) -> bool()).
 
108
-spec is_comment(icode_instr()) -> bool().
108
109
is_comment(Instr) ->
109
110
  hipe_icode:is_comment(Instr).
110
111
 
111
112
%% True if instr is just a jump (no side-effects).
112
 
-spec(is_goto/1 :: (icode_instr()) -> bool()).
 
113
-spec is_goto(icode_instr()) -> bool().
113
114
is_goto(Instr) ->
114
115
  hipe_icode:is_goto(Instr).
115
116
 
116
 
-spec(is_branch/1 :: (icode_instr()) -> bool()).
 
117
-spec is_branch(icode_instr()) -> bool().
117
118
is_branch(Instr) ->
118
119
  hipe_icode:is_branch(Instr).
119
120
 
120
 
-spec(is_pure_branch/1 :: (icode_instr()) -> bool()).
 
121
-spec is_pure_branch(icode_instr()) -> bool().
121
122
is_pure_branch(Instr) ->
122
123
  case Instr of
123
124
    #icode_if{} -> true;
139
140
    #icode_comment{} -> false
140
141
  end.
141
142
 
142
 
-spec(is_phi/1 :: (icode_instr()) -> bool()).
 
143
-spec is_phi(icode_instr()) -> bool().
143
144
is_phi(I) ->
144
145
  hipe_icode:is_phi(I).
145
146
 
157
158
 
158
159
%%----------------------------------------------------------------------------
159
160
 
160
 
-spec(pp/1 :: (#cfg{}) -> 'ok').
 
161
-spec pp(#cfg{}) -> 'ok'.
 
162
 
161
163
pp(CFG) ->
162
164
  hipe_icode_pp:pp(cfg_to_linear(CFG)).
163
165
 
164
 
-spec(pp/2 :: (io_device(), #cfg{}) -> 'ok').
 
166
-spec pp(io_device(), #cfg{}) -> 'ok'.
 
167
 
165
168
pp(Dev, CFG) ->
166
169
  hipe_icode_pp:pp(Dev, cfg_to_linear(CFG)).
167
170
 
168
171
%%----------------------------------------------------------------------------
169
172
 
170
 
-spec(cfg_to_linear/1 :: (#cfg{}) -> #icode{}).
 
173
-spec cfg_to_linear(#cfg{}) -> #icode{}.
171
174
cfg_to_linear(CFG) ->
172
175
  Code = linearize_cfg(CFG),
173
176
  IsClosure = is_closure(CFG),