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

« back to all changes in this revision

Viewing changes to lib/hipe/icode/hipe_icode_pp.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) 2003 by Erik Stenman.  
3
 
%% -*- erlang-indent-level: 2 -*-
4
4
%% ====================================================================
5
5
%%  Filename :  hipe_icode_pp.erl
6
6
%%  Module   :  hipe_icode_pp
7
7
%%  Purpose  :  Pretty-printer for Icode.
8
8
%%  Notes    : 
9
 
%%  History  :  * 2003-04-16  (stenman@epfl.ch): 
10
 
%%               Created.
 
9
%%  History  :  * 2003-04-16 (stenman@epfl.ch): Created.
11
10
%%  CVS      :
12
 
%%              $Author: tobiasl $
13
 
%%              $Date: 2003/04/23 12:31:24 $
14
 
%%              $Revision: 1.3 $
 
11
%%              $Author$
 
12
%%              $Date$
 
13
%%              $Revision$
15
14
%% ====================================================================
16
 
%%  Exports  :
 
15
%% 
 
16
%% @doc
 
17
%%   Icode Pretty-Printer.
 
18
%% @end
17
19
%%
18
 
%% ____________________________________________________________________
19
 
%% 
20
 
%%@doc Icode PrettyPrinter
21
 
%% 
22
 
%%@end
23
 
%% ____________________________________________________________________
 
20
%% ====================================================================
 
21
 
24
22
-module(hipe_icode_pp).
25
 
-export([pp/1,  pp/2, pp_instrs/2, pp_exit/1]).
26
 
 
27
 
 
28
 
 
29
 
%% - changed pp_instr => pp_instrs + pp_instr as in RTL and Sparc
30
 
%% - added pp_exit/1 as in RTL + Sparc.
31
 
 
32
 
%%@spec (Icode::hipe_icode:icode()) -> ok
 
23
 
 
24
-export([pp/1, pp/2, pp_block/1]).
 
25
 
 
26
-ifdef(DEBUG_ICODE).
 
27
-export([pp_instrs/2, pp_exit/1]).
 
28
-endif.
 
29
 
 
30
-include("hipe_icode.hrl").
 
31
 
 
32
%%---------------------------------------------------------------------
 
33
 
 
34
%% @spec pp(Icode::hipe_icode:icode()) -> ok
33
35
%%
34
 
%%@doc Prettyprints Linear Icode on stdout.
35
 
%%<p> Badly formed or unknown instructions are printed suronded by three stars "***".</p>
 
36
%% @doc Prettyprints linear Icode on stdout.
 
37
%%  <p> Badly formed or unknown instructions are printed surrounded
 
38
%%      by three stars "***".</p>
36
39
pp(Icode) ->
37
40
  pp(standard_io, Icode).
38
41
 
39
 
%%@spec (IoDevice::iodevice(), Icode::hipe_icode:icode()) -> ok
 
42
%% @spec pp(IoDevice::iodevice(), Icode::hipe_icode:icode()) -> ok
40
43
%%
41
 
%%@doc Prettyprints Linear Icode on IoDevice.
42
 
%%<p> Badly formed or unknown instructions are printed suronded by three stars "***".</p>
 
44
%% @doc Prettyprints linear Icode on IoDevice.
 
45
%%  <p> Badly formed or unknown instructions are printed surrounded by
 
46
%%      three stars "***".</p>
43
47
pp(Dev, Icode) ->
44
 
  {Mod, Fun, _Arity} = hipe_icode:icode_fun(Icode),
45
 
  Args =  hipe_icode:icode_params(Icode),
46
 
  io:format(Dev, "~w:~w(", [Mod, Fun]),
 
48
  {Mod, Fun, Arity} = hipe_icode:icode_fun(Icode),
 
49
  Args = hipe_icode:icode_params(Icode),
 
50
  io:format(Dev, "~w:~w/~w(", [Mod, Fun, Arity]),
47
51
  pp_args(Dev, Args),
48
52
  io:format(Dev, ") ->~n", []),
49
 
  io:format(Dev, "%% Info:~w\n",
 
53
  Info = lists:map(fun(X)-> case X of
 
54
                              {arg_type, AT} -> 
 
55
                                {arg_type, 
 
56
                                 [erl_types:t_to_string(Y)
 
57
                                  ||Y <- AT]};
 
58
                              _  -> 
 
59
                                X
 
60
                            end
 
61
                   end,
 
62
                   hipe_icode:icode_info(Icode)),
 
63
  io:format(Dev, "%% Info:~p\n",
50
64
            [[case hipe_icode:icode_is_closure(Icode) of
51
65
                true -> 'Closure'; 
52
66
                false -> 'Not a closure'
55
69
                true -> 'Leaf function'; 
56
70
                false -> 'Not a leaf function'
57
71
              end |
58
 
              hipe_icode:icode_info(Icode)]]),
 
72
              Info]]),
59
73
  pp_instrs(Dev, hipe_icode:icode_code(Icode)),
60
74
  io:format(Dev, "%% Data:\n", []),
61
75
  hipe_data_pp:pp(Dev, hipe_icode:icode_data(Icode), icode, "").
62
76
 
63
 
%%@spec (iodevice(), [hipe_icode:icode_instruction()]) -> ok
 
77
pp_block(Code) ->
 
78
  pp_instrs(standard_io, Code).
 
79
 
 
80
%% @spec pp_instrs(iodevice(), [hipe_icode:icode_instruction()]) -> ok
64
81
%%
65
 
%%@doc Prettyprints a list of Icode instrucitons.
66
 
%% Badly formed or unknown instructions are printed suronded by three stars "***".
 
82
%% @doc Prettyprints a list of Icode instructions. Badly formed or
 
83
%%      unknown instructions are printed surrounded by three stars
 
84
%%      "***".
67
85
pp_instrs(_Dev, []) ->
68
86
  ok;
69
87
pp_instrs(Dev, [I|Is]) ->
75
93
  end,
76
94
  pp_instrs(Dev, Is).
77
95
 
78
 
%% ____________________________________________________________________
79
 
%% 
80
 
%%@spec (Icode::hipe_icode:icode()) -> ok
 
96
%%---------------------------------------------------------------------
 
97
 
 
98
-ifdef(DEBUG_ICODE).
 
99
 
 
100
%% @spec (Icode::hipe_icode:icode()) -> ok
81
101
%%
82
 
%%@doc Prettyprints Linear Icode on stdout.
83
 
%% Bad formed or unknown instructions generates an exception.
 
102
%% @doc Prettyprints linear Icode on stdout.
 
103
%%      Badly formed or unknown instructions generate an exception.
84
104
pp_exit(Icode) ->
85
105
  pp_exit(standard_io, Icode).
86
106
 
87
 
%%@spec (IoDevice::iodevice(), Icode::hipe_icode:icode()) -> ok
 
107
%% @clear
 
108
%% @spec (IoDevice::iodevice(), Icode::hipe_icode:icode()) -> ok
88
109
%%
89
 
%%@doc Prettyprints Linear Icode on IoDevice.
90
 
%% Bad formed or unknown instructions generates an exception.
 
110
%% @doc Prettyprints linear Icode on IoDevice.
 
111
%%      Badly formed or unknown instructions generate an exception.
 
112
%% @end
91
113
pp_exit(Dev, Icode) ->
92
114
  {Mod, Fun, _Arity} = hipe_icode:icode_fun(Icode),
93
 
  Args =  hipe_icode:icode_params(Icode),
 
115
  Args = hipe_icode:icode_params(Icode),
94
116
  io:format(Dev, "~w:~w(", [Mod, Fun]),
95
117
  pp_args(Dev, Args),
96
118
  io:format(Dev, ") ->~n", []),
97
119
  pp_instrs_exit(Dev, hipe_icode:icode_code(Icode)).
98
120
 
99
 
%% Prettyprints a list of Icode instrucitons.
100
 
%% Badly formed or unknown instructions generates an exception.
101
121
pp_instrs_exit(_Dev, []) ->
102
122
  ok;
103
123
pp_instrs_exit(Dev, [I|Is]) ->
109
129
  end,
110
130
  pp_instrs_exit(Dev, Is).
111
131
 
112
 
%% ____________________________________________________________________
113
 
%% 
 
132
-endif.
 
133
 
 
134
%%---------------------------------------------------------------------
 
135
 
114
136
pp_instr(Dev, I) ->
115
 
  case hipe_icode:type(I) of 
116
 
    label ->
117
 
      io:format(Dev, "~p: ", [hipe_icode:label_name(I)]),
118
 
      case  hipe_icode:info(I) of
119
 
        [] -> io:format(Dev, "~n",[]);
120
 
        Info -> io:format(Dev, "~w~n", [Info])
121
 
      end;
122
 
 
123
 
    comment ->
124
 
      io:format(Dev, "    % ~p~n", [hipe_icode:comment_text(I)]);
125
 
 
126
 
    phi ->
 
137
  case I of 
 
138
    #label{} ->
 
139
      io:format(Dev, "~p:~n", [hipe_icode:label_name(I)]);
 
140
    #comment{} ->
 
141
      Txt = hipe_icode:comment_text(I),
 
142
      Str = case io_lib:deep_char_list(Txt) of
 
143
              true -> Txt;
 
144
              false -> io_lib:format("~p", [Txt])
 
145
            end,
 
146
      io:format(Dev, "    % ~s~n", [Str]);
 
147
    #phi{} ->
127
148
      io:format(Dev, "    ", []),
128
149
      pp_arg(Dev, hipe_icode:phi_dst(I)),
129
150
      io:format(Dev, " := phi(", []),
130
 
      pp_args(Dev, hipe_icode:phi_args(I)),
 
151
      pp_phi_args(Dev, hipe_icode:phi_arglist(I)),
131
152
      io:format(Dev, ")~n", []);
132
 
 
133
 
    mov ->
 
153
    #move{} ->
134
154
      io:format(Dev, "    ", []),
135
 
      pp_arg(Dev, hipe_icode:mov_dst(I)),
 
155
      pp_arg(Dev, hipe_icode:move_dst(I)),
136
156
      io:format(Dev, " := ", []),
137
 
      pp_arg(Dev, hipe_icode:mov_src(I)),
 
157
      pp_arg(Dev, hipe_icode:move_src(I)),
138
158
      io:format(Dev, "~n", []);
139
 
 
140
 
    call ->
141
 
      case hipe_icode:call_in_guard(I) of
142
 
        true ->
143
 
          io:format(Dev, " <G>", []);
144
 
        _ ->
145
 
          io:format(Dev, "    ", [])
146
 
      end,
147
 
      case hipe_icode:call_dst(I) of
148
 
        [] ->
 
159
    #call{} ->
 
160
      io:format(Dev, "    ", []),
 
161
      case hipe_icode:call_dstlist(I) of
 
162
        [] -> %% result is unused -- e.g. taken out by dead code elimination
149
163
          io:format(Dev, "_ := ", []);
150
 
        Dst ->
151
 
          pp_args(Dev, Dst),
 
164
        DstList ->
 
165
          pp_args(Dev, DstList),
152
166
          io:format(Dev, " := ", [])
153
167
      end,
154
 
      hipe_icode_primops:pp(hipe_icode:call_fun(I), Dev),
155
 
      io:format(Dev, "(", []),
156
 
      pp_args(Dev, hipe_icode:call_args(I)),
 
168
      pp_fun(Dev, hipe_icode:call_fun(I),
 
169
             hipe_icode:call_args(I),
 
170
             hipe_icode:call_type(I),
 
171
             hipe_icode:call_in_guard(I)),
157
172
      case hipe_icode:call_continuation(I) of
158
173
        [] ->
159
 
          io:format(Dev, ") (~w)", [hipe_icode:call_type(I)]);
 
174
          ok;
160
175
        CC ->
161
 
          io:format(Dev, ") (~w) -> ~w",
162
 
                    [hipe_icode:call_type(I),CC])
 
176
          io:format(Dev, " -> ~w", [CC])
163
177
      end,
164
 
 
165
 
      case hipe_icode:call_fail(I) of
 
178
      case hipe_icode:call_fail_label(I) of
166
179
        [] ->  io:format(Dev, "~n", []);
167
180
        Fail ->  io:format(Dev, ", #fail ~w~n", [Fail])
168
181
      end;
169
 
    enter ->
 
182
    #enter{} ->
170
183
      io:format(Dev, "    ", []),
171
 
      case hipe_icode:enter_fun(I) of
172
 
        {Mod, Fun, _Arity} ->
173
 
          io:format(Dev, "~w:~w(", [Mod, Fun]);
174
 
        {Fun, _Arity} ->
175
 
          io:format(Dev, "~w(", [Fun]);
176
 
        Fun ->
177
 
          io:format(Dev, "~w(", [Fun])
178
 
      end,
179
 
      pp_args(Dev, hipe_icode:enter_args(I)),
180
 
      io:format(Dev, ") (~w) ~n", 
181
 
                [hipe_icode:enter_type(I)]);
182
 
    return ->
 
184
      pp_fun(Dev, hipe_icode:enter_fun(I),
 
185
             hipe_icode:enter_args(I),
 
186
             hipe_icode:enter_type(I)),
 
187
      io:format(Dev, "~n", []);
 
188
    #return{} ->
183
189
      io:format(Dev, "    return(", []),
184
190
      pp_args(Dev, hipe_icode:return_vars(I)),
185
191
      io:format(Dev, ")~n", []);
186
 
    pushcatch ->
187
 
      io:format(Dev, "    pushcatch -> ~w cont ~w~n", 
188
 
                [hipe_icode:pushcatch_label(I), 
189
 
                 hipe_icode:pushcatch_successor(I)]);
190
 
    restore_catch ->
 
192
    #begin_try{} ->
 
193
      io:format(Dev, "    begin_try -> ~w cont ~w~n", 
 
194
                [hipe_icode:begin_try_label(I), 
 
195
                 hipe_icode:begin_try_successor(I)]);
 
196
    #begin_handler{} ->
191
197
      io:format(Dev, "    ", []),
192
 
      case hipe_icode:restore_catch_type(I) of
193
 
        'try' ->
194
 
          pp_args(Dev, [hipe_icode:restore_catch_reason_dst(I),
195
 
                        hipe_icode:restore_catch_type_dst(I)]);
196
 
        'catch' ->
197
 
          pp_arg(Dev, hipe_icode:restore_catch_reason_dst(I))
198
 
      end,
199
 
      io:format(Dev, " := restore_catch(~w)~n",
200
 
                [hipe_icode:restore_catch_label(I)]);
201
 
    remove_catch ->
202
 
      io:format(Dev, "    remove_catch(~w)~n", 
203
 
                [hipe_icode:remove_catch_label(I)]);
204
 
    fail ->
205
 
      Type = case hipe_icode:fail_type(I) of
206
 
               fault2 -> fault;
207
 
               T -> T
208
 
             end,
 
198
      pp_args(Dev, hipe_icode:begin_handler_dstlist(I)),
 
199
      io:format(Dev, " := begin_handler()~n",[]);
 
200
    #end_try{} ->
 
201
      io:format(Dev, "    end_try~n", []);
 
202
    #fail{} ->
 
203
      Type = hipe_icode:fail_class(I),
209
204
      io:format(Dev, "    fail(~w, [", [Type]),
210
 
      pp_args(Dev, hipe_icode:fail_reason(I)),
211
 
      io:put_chars(Dev, "])\n");
212
 
    'if' ->
 
205
      pp_args(Dev, hipe_icode:fail_args(I)),
 
206
      case hipe_icode:fail_label(I) of
 
207
        [] ->  io:put_chars(Dev, "])\n");
 
208
        Fail ->  io:format(Dev, "]) -> ~w\n", [Fail])
 
209
      end;
 
210
    #'if'{} ->
213
211
      io:format(Dev, "    if ~w(", [hipe_icode:if_op(I)]),
214
212
      pp_args(Dev, hipe_icode:if_args(I)),
215
213
      io:format(Dev, ") then ~p (~.2f) else ~p~n", 
216
 
                [hipe_icode:if_true_label(I), hipe_icode:if_pred(I),  hipe_icode:if_false_label(I)]);
217
 
    switch_val ->
 
214
                [hipe_icode:if_true_label(I), hipe_icode:if_pred(I),
 
215
                 hipe_icode:if_false_label(I)]);
 
216
    #switch_val{} ->
218
217
      io:format(Dev, "    switch_val ",[]),
219
218
      pp_arg(Dev, hipe_icode:switch_val_arg(I)),
220
219
      pp_switch_cases(Dev, hipe_icode:switch_val_cases(I)),
221
220
      io:format(Dev, "    fail -> ~w\n", 
222
221
                [hipe_icode:switch_val_fail_label(I)]);
223
 
    switch_tuple_arity ->
 
222
    #switch_tuple_arity{} ->
224
223
      io:format(Dev, "    switch_tuple_arity ",[]),
225
224
      pp_arg(Dev, hipe_icode:switch_tuple_arity_arg(I)),
226
225
      pp_switch_cases(Dev,hipe_icode:switch_tuple_arity_cases(I)),
227
226
      io:format(Dev, "    fail -> ~w\n", 
228
227
                [hipe_icode:switch_tuple_arity_fail_label(I)]);
229
 
    type ->
 
228
    #type{} ->
230
229
      io:format(Dev, "    if is_", []),
231
230
      pp_type(Dev, hipe_icode:type_type(I)),
232
231
      io:format(Dev, "(", []),
233
 
      pp_arg(Dev, hipe_icode:type_var(I)),
 
232
      pp_args(Dev, hipe_icode:type_args(I)),
234
233
      io:format(Dev, ") then ~p (~.2f) else ~p~n", 
235
234
                [hipe_icode:type_true_label(I), hipe_icode:type_pred(I), 
236
235
                 hipe_icode:type_false_label(I)]);
237
 
    goto ->
 
236
    #goto{} ->
238
237
      io:format(Dev, "    goto ~p~n", [hipe_icode:goto_label(I)]);
239
 
    fmov ->
 
238
    #fmove{} ->
240
239
      io:format(Dev, "    ", []),
241
 
      pp_arg(Dev, hipe_icode:fmov_dst(I)),
 
240
      pp_arg(Dev, hipe_icode:fmove_dst(I)),
242
241
      io:format(Dev, " f:= ", []),
243
 
      pp_arg(Dev, hipe_icode:fmov_src(I)),
 
242
      pp_arg(Dev, hipe_icode:fmove_src(I)),
244
243
      io:format(Dev, "~n", [])
245
244
  end.
246
245
 
 
246
pp_fun(Dev, Fun, Args, Type) ->
 
247
  pp_fun(Dev, Fun, Args, Type, false).
 
248
 
 
249
pp_fun(Dev, Fun, Args, Type, Guard) ->
 
250
  case Type of
 
251
    primop ->
 
252
      hipe_icode_primops:pp(Fun, Dev);
 
253
    local ->
 
254
      {_,F,A} = Fun,
 
255
      io:format(Dev, "~w/~w", [F, A]);
 
256
    remote ->
 
257
      {M,F,A} = Fun,
 
258
      io:format(Dev, "~w:~w/~w", [M, F, A])
 
259
  end,
 
260
  io:format(Dev, "(", []),
 
261
  pp_args(Dev, Args),
 
262
  case Guard of
 
263
    true ->
 
264
      case Type of
 
265
        primop ->
 
266
          io:format(Dev, ") (primop,guard)", []);
 
267
        _ ->
 
268
          io:format(Dev, ") (guard)", [])
 
269
      end;
 
270
    false ->
 
271
      case Type of
 
272
        primop ->
 
273
          io:format(Dev, ") (primop)", []);
 
274
        _ ->
 
275
          io:format(Dev, ")", [])
 
276
      end
 
277
  end.
 
278
 
 
279
pp_arg(Dev, {var, V, {T, R}}) ->
 
280
  io:format(Dev, "v~p (~s, ~s)", [V, erl_types:t_to_string(T), hipe_icode_range_an:to_string(R)]);
247
281
pp_arg(Dev, {var, V, T}) ->
248
 
  case erl_types:t_is_undefined(T) of
249
 
    true->
250
 
      io:format(Dev, "v~p", [V]);
251
 
    _ ->
252
 
      io:format(Dev, "v~p (~s)", [V, erl_types:t_to_string(T)])
253
 
  end;
 
282
  io:format(Dev, "v~p (~s)", [V, erl_types:t_to_string(T)]);
254
283
pp_arg(Dev, {var, V}) ->
255
284
  io:format(Dev, "v~p", [V]);
256
285
pp_arg(Dev, {fvar, V}) ->
258
287
pp_arg(Dev, {reg, V}) -> 
259
288
  io:format(Dev, "r~p", [V]);
260
289
pp_arg(Dev, C) ->
261
 
  io:format(Dev, "~p", [hipe_icode:const_value(C)]).
 
290
  Const = hipe_icode:const_value(C), 
 
291
  case is_string(Const) of
 
292
    true ->
 
293
      io:format(Dev, "~p", [Const]);
 
294
    false ->
 
295
      io:format(Dev, "~w", [Const])
 
296
  end.
262
297
 
263
298
pp_args(_Dev, []) -> ok;
264
299
pp_args(Dev, [A]) ->
268
303
  io:format(Dev, ", ", []),
269
304
  pp_args(Dev, Args).
270
305
 
 
306
pp_phi_args(_Dev, []) -> ok;
 
307
pp_phi_args(Dev, [{Pred,A}]) ->
 
308
  io:format(Dev, "{~w, ", [Pred]),
 
309
  pp_arg(Dev, A),
 
310
  io:format(Dev, "}", []);
 
311
pp_phi_args(Dev, [{Pred,A}|Args]) ->
 
312
  io:format(Dev, "{~w, ", [Pred]),
 
313
  pp_arg(Dev, A),
 
314
  io:format(Dev, "}, ", []),
 
315
  pp_phi_args(Dev, Args);
 
316
pp_phi_args(Dev, Args) ->
 
317
  pp_args(Dev, Args).
 
318
 
271
319
pp_type(Dev, T) ->
272
320
  io:format(Dev, "~w", [T]).
273
321
 
293
341
  pp_switch_cases(Dev, Ls, NewPos);
294
342
pp_switch_cases(_Dev, [], _) -> ok.
295
343
 
296
 
 
 
344
is_string([X|Rest]) when X > 0, X < 256 ->
 
345
  is_string(Rest);
 
346
is_string([]) ->
 
347
  true;
 
348
is_string(_) ->
 
349
  false.