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

« back to all changes in this revision

Viewing changes to lib/hipe/sparc/0OLD/hipe_sparc_pp.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-07 15:07:37 UTC
  • mfrom: (1.2.1 upstream) (5.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090507150737-i4yb5elwinm7r0hc
Tags: 1:13.b-dfsg1-1
* Removed another bunch of non-free RFCs from original tarball
  (closes: #527053).
* Fixed build-dependencies list by adding missing comma. This requires
  libsctp-dev again. Also, added libsctp1 dependency to erlang-base and
  erlang-base-hipe packages because the shared library is loaded via
  dlopen now and cannot be added using dh_slibdeps (closes: #526682).
* Weakened dependency of erlang-webtool on erlang-observer to recommends
  to avoid circular dependencies (closes: #526627).
* Added solaris-i386 to HiPE enabled architectures.
* Made script sources in /usr/lib/erlang/erts-*/bin directory executable,
  which is more convenient if a user wants to create a target Erlang system.
* Shortened extended description line for erlang-dev package to make it
  fit 80x25 terminals.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%% -*- erlang-indent-level: 2 -*-
2
 
%% ====================================================================
3
 
%%  Filename :  hipe_sparc_pp.erl
4
 
%%  Module   :  hipe_sparc_pp
5
 
%%  Purpose  :  Pretty printer for sparc code
6
 
%%  Notes    : 
7
 
%%  History  :  * 2001-10-25 Erik Johansson (happi@csd.uu.se): 
8
 
%%               Created.
9
 
%%  CVS      :
10
 
%%              $Author: kostis $
11
 
%%              $Date: 2007/12/20 00:16:37 $
12
 
%%              $Revision: 1.2 $
13
 
%% ====================================================================
14
 
%%  Exports  :
15
 
%%              pp/1,        Pretty prints linear SPARC code.
16
 
%%              pp/2,        -- "" -- To a file
17
 
%%              pp_instr/1,  Pretty prints a SPARC instruction.
18
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
19
 
 
20
 
-module(hipe_sparc_pp).
21
 
-export([pp/1,          %% Pretty prints linear SPARC code.
22
 
         pp/2]).        %% -- "" -- To a device (file)
23
 
%%-export([pp_instr/1]). %% Pretty prints a SPARC instruction.
24
 
 
25
 
-include("../main/hipe.hrl").
26
 
-include("hipe_sparc.hrl").
27
 
 
28
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
29
 
%%
30
 
%% Pretty printer
31
 
%%
32
 
%% - pp/1: pretty prints linear SPARC code
33
 
%%
34
 
 
35
 
pp(Sparc) ->
36
 
  pp(Sparc, standard_io).
37
 
 
38
 
pp(Sparc, Dev) ->
39
 
  {M, F, A} = hipe_sparc:sparc_fun(Sparc),
40
 
  Fname = atom_to_list(M)++"_"++atom_to_list(F)++"_"++integer_to_list(A),
41
 
   case hipe_sparc:sparc_is_closure(Sparc) of
42
 
     true ->
43
 
       io:format(Dev, "! Closure\n", []);
44
 
     _ -> ok
45
 
   end,
46
 
   case hipe_sparc:sparc_is_leaf(Sparc) of
47
 
     true ->
48
 
       io:format(Dev, "! Leaf function\n", []);
49
 
     _ -> ok
50
 
   end,
51
 
  io:format(Dev, ".section    \".text\"~n", []),
52
 
  io:format(Dev, "    .align 4~n", []),
53
 
  io:format(Dev, "    .global ", []),
54
 
  io:format(Dev, "~s~n", [Fname]),
55
 
  io:format(Dev, ".section    \".data\"\n", []),
56
 
  hipe_data_pp:pp(Dev, hipe_sparc:sparc_data(Sparc), sparc, Fname), 
57
 
  io:format(Dev, ".section    \".code\"\n", []),
58
 
  io:format(Dev, "~s:~n", [Fname]),
59
 
  pp_instrs(hipe_sparc:sparc_code(Sparc), Dev, Fname),
60
 
  io:format(Dev, "~n~n", []).
61
 
 
62
 
pp_instrs([], _Dev, _Fname) ->
63
 
  ok;
64
 
pp_instrs([I|Is], Dev, Fname) ->
65
 
  pp_instr(I, Dev, Fname),
66
 
  pp_instrs(Is, Dev, Fname).
67
 
 
68
 
 
69
 
%% pp_instr(I) ->
70
 
%%   pp_instr(I, standard_io, "").
71
 
 
72
 
pp_instr(I, Dev, Pre) ->
73
 
  case I of
74
 
    #pseudo_return{} ->
75
 
      io:format(Dev, "    retl ! ", []),
76
 
      pp_args(Dev, hipe_sparc:pseudo_return_regs(I)),
77
 
      io:format(Dev, "~n", []);
78
 
    #pseudo_enter{} ->
79
 
      io:format(Dev, "!    pseudo_enter ", []),
80
 
      pp_target(Dev, 
81
 
                hipe_sparc:pseudo_enter_target(I),
82
 
                hipe_sparc:pseudo_enter_is_known(I)),
83
 
      io:format(Dev, " ! (",[]),
84
 
      pp_args(Dev, hipe_sparc:pseudo_enter_args(I)),
85
 
      io:format(Dev, ")~n", []);
86
 
%%  #pseudo_push{} ->
87
 
%%    io:format(Dev, "!    pseudo_push ", []),
88
 
%%    pp_arg(Dev, hipe_sparc:pseudo_push_reg(I)),
89
 
%%    io:format(Dev, "~n", []);
90
 
    #pseudo_spill{} ->
91
 
      io:format(Dev, "!    pseudo_spill ", []),
92
 
      pp_arg(Dev, hipe_sparc:pseudo_spill_reg(I)),
93
 
      io:format(Dev, ", SP<", []),
94
 
      pp_arg(Dev, hipe_sparc:pseudo_spill_pos(I)),
95
 
      io:format(Dev, ">~n", []);
96
 
    #pseudo_unspill{} ->
97
 
      io:format(Dev, "!    pseudo_unspill ", []),
98
 
      pp_arg(Dev, hipe_sparc:pseudo_unspill_reg(I)),
99
 
      io:format(Dev, ", SP<", []),
100
 
      pp_arg(Dev, hipe_sparc:pseudo_unspill_pos(I)),
101
 
      io:format(Dev, ">~n", []);
102
 
    #pseudo_pop{} ->
103
 
      io:format(Dev, "!    pseudo_get_arg ", []),
104
 
      pp_arg(Dev, hipe_sparc:pseudo_pop_index(I)),
105
 
      io:format(Dev, ", ", []),
106
 
      pp_arg(Dev, hipe_sparc:pseudo_pop_reg(I)),
107
 
      io:format(Dev, "~n", []);
108
 
    #label{} ->
109
 
      io:format(Dev, ".~s_~w:~n", [Pre, hipe_sparc:label_name(I)]);
110
 
    #comment{} ->
111
 
      io:format(Dev, "    ! ~p~n", [hipe_sparc:comment_text(I)]);
112
 
    #nop{} ->
113
 
      io:format(Dev, "    nop~n", []);
114
 
    #move{} ->
115
 
      io:format(Dev, "    mov ", []),
116
 
      pp_arg(Dev, hipe_sparc:move_src(I)),
117
 
      io:format(Dev, ", ", []),
118
 
      pp_arg(Dev, hipe_sparc:move_dest(I)),
119
 
      io:format(Dev, "~n", []);
120
 
    #multimove{} ->
121
 
      Srcs = hipe_sparc:multimove_src(I),
122
 
      Dsts = hipe_sparc:multimove_dest(I),
123
 
      case length(Srcs) of
124
 
        1 ->
125
 
          io:format(Dev, "    mov ", []),
126
 
          pp_arg(Dev, hd(Srcs)),
127
 
          io:format(Dev, ", ", []),
128
 
          pp_arg(Dev, hd(Dsts)),
129
 
          io:format(Dev, " ! mmove ~n", []);
130
 
        _ ->
131
 
          io:format(Dev, "    ! Multimove   !~n",[]),
132
 
          pp_mmoves(Dev, Srcs, Dsts),
133
 
          io:format(Dev, "    ! End mmove   !~n",[])
134
 
      end;
135
 
    #alu{} ->
136
 
      io:format(Dev, "    ", []),
137
 
      pp_alu_op(Dev, hipe_sparc:alu_operator(I)),
138
 
      io:format(Dev, " ", []),
139
 
      pp_arg(Dev, hipe_sparc:alu_src1(I)),
140
 
      io:format(Dev, ", ", []),
141
 
      pp_arg(Dev, hipe_sparc:alu_src2(I)),
142
 
      io:format(Dev, ", ", []),
143
 
      pp_arg(Dev, hipe_sparc:alu_dest(I)),
144
 
      io:format(Dev, "~n", []);
145
 
    #alu_cc{} ->
146
 
      io:format(Dev, "    ", []),
147
 
      pp_alu_op(Dev, hipe_sparc:alu_cc_operator(I)),
148
 
      io:format(Dev, "cc ", []),
149
 
      pp_arg(Dev, hipe_sparc:alu_cc_src1(I)),
150
 
      io:format(Dev, ", ", []),
151
 
      pp_arg(Dev, hipe_sparc:alu_cc_src2(I)),
152
 
      io:format(Dev, ", ", []),
153
 
      pp_arg(Dev, hipe_sparc:alu_cc_dest(I)),
154
 
      io:format(Dev, "~n", []);
155
 
%%  #br{} ->
156
 
%%    io:format(Dev, "    br", []),
157
 
%%    pp_regcc(Dev, hipe_sparc:br_regcond(I)),
158
 
%%    pp_annul(Dev, hipe_sparc:br_annul(I)),
159
 
%%    pp_pred(Dev, hipe_sparc:br_taken(I)),
160
 
%%    io:format(Dev, " ", []),
161
 
%%    pp_arg(Dev, hipe_sparc:br_reg(I)),
162
 
%%    pp_target(Dev, 
163
 
%%              hipe_sparc:br_true_label(I),
164
 
%%              hipe_sparc:br_false_label(I),
165
 
%%              Pre),
166
 
%%    io:format(Dev, "~n", []);
167
 
    #b{} ->
168
 
      io:format(Dev, "    b", []),
169
 
      pp_cc(Dev, hipe_sparc:b_cond(I)),
170
 
      pp_annul(Dev, hipe_sparc:b_annul(I)),
171
 
      pp_pred(Dev, hipe_sparc:b_taken(I)),
172
 
      io:format(Dev, " %icc",[]),
173
 
      pp_target(Dev, 
174
 
                hipe_sparc:b_true_label(I),
175
 
                hipe_sparc:b_false_label(I),
176
 
                Pre),
177
 
      io:format(Dev, "~n", []);
178
 
    #goto{} ->
179
 
      io:format(Dev, "    ba .~s_~w~n", [Pre, hipe_sparc:goto_label(I)]);
180
 
    #jmp{} ->
181
 
      io:format(Dev, "    jmpl ", []),
182
 
      pp_arg(Dev, hipe_sparc:jmp_target(I)),
183
 
      io:format(Dev, "+", []),
184
 
      pp_arg(Dev, hipe_sparc:jmp_off(I)),
185
 
      io:format(Dev, ", %g0 ! (", []),
186
 
      pp_args(Dev, hipe_sparc:jmp_args(I)),
187
 
      io:format(Dev, ") ", []),
188
 
      case hipe_sparc:jmp_destinations(I) of
189
 
        [] -> io:format(Dev, "~n", []);
190
 
        Lbls -> pp_switch_labels(Dev,Lbls, Pre),
191
 
                io:format(Dev, "~n", [])
192
 
      end;
193
 
    %% #jmp_link{} ->
194
 
    #call_link{} ->
195
 
      io:format(Dev, "    call ", []),
196
 
      pp_target(Dev, 
197
 
                hipe_sparc:call_link_target(I),
198
 
                hipe_sparc:call_link_is_known(I)),
199
 
      io:format(Dev, " ! (",[]),
200
 
      pp_args(Dev, hipe_sparc:call_link_args(I)),
201
 
      io:format(Dev, ") <", []),
202
 
      pp_args(Dev, hipe_sparc:call_link_dests(I)),
203
 
      io:format(Dev, ">", []),
204
 
      case hipe_sparc:call_link_fail(I) of
205
 
        [] -> true;
206
 
        L ->
207
 
          io:format(Dev, " fail to ~s_~w", [Pre,L])
208
 
      end,
209
 
      %% io:format(Dev, "~n", []),
210
 
      case hipe_sparc:call_link_continuation(I) of
211
 
        [] -> ok;
212
 
        CL -> io:format(Dev, "   (~s_~w)", [Pre,CL])
213
 
      end,
214
 
      hipe_sparc:pp_sdesc(Dev, hipe_sparc:call_link_stack_desc(I)),
215
 
      io:format(Dev, "~n", []);
216
 
    #load{} ->
217
 
      io:format(Dev, "    ", []),
218
 
      pp_load_op(Dev, hipe_sparc:load_type(I)),
219
 
      io:format(Dev, " [", []),
220
 
      pp_arg(Dev, hipe_sparc:load_src(I)),
221
 
      io:format(Dev, "+", []),
222
 
      pp_arg(Dev, hipe_sparc:load_off(I)),
223
 
      io:format(Dev, "], ", []),
224
 
      pp_arg(Dev, hipe_sparc:load_dest(I)),
225
 
      io:format(Dev, "~n", []);
226
 
    #load_atom{} ->
227
 
      Atom = hipe_sparc:load_atom_atom(I),
228
 
      io:format(Dev, "   sethi %hi(~w), ", [hipe_bifs:atom_to_word(Atom)]),
229
 
      pp_arg(Dev, hipe_sparc:load_atom_dest(I)),
230
 
      io:format(Dev, "~n   or ",[]),
231
 
      pp_arg(Dev, hipe_sparc:load_atom_dest(I)),
232
 
      io:format(Dev, ",  %lo(~w), ", [hipe_bifs:atom_to_word(Atom)]),
233
 
      pp_arg(Dev, hipe_sparc:load_atom_dest(I)),
234
 
      io:format(Dev, " ! load_atom('~w') ~n", [Atom]);
235
 
    #load_word_index{} ->
236
 
      io:format(Dev, "    mov word_index(~s_dl_~w, ~w), ", 
237
 
                [Pre, hipe_sparc:load_word_index_block(I), hipe_sparc:load_word_index_index(I)]),
238
 
      pp_arg(Dev, hipe_sparc:load_word_index_dest(I)),
239
 
      io:format(Dev, "~n",[]);
240
 
    #load_address{} ->
241
 
      Address = hipe_sparc:load_address_addr(I),
242
 
      Type = hipe_sparc:load_address_type(I), 
243
 
      case Type of
244
 
        function ->
245
 
          case Address of
246
 
            {M, F, A} -> 
247
 
              io:format(Dev, "    sethi %hi(~w_~w_~w), ", [M, F, A]),
248
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I)),
249
 
              io:format(Dev, "~n    or  ", []),
250
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I)),
251
 
              io:format(Dev, ", %lo(~w_~w_~w), ", [M, F, A]),
252
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I));
253
 
            {F, A} -> 
254
 
              io:format(Dev, "    sethi %hi(~w_~w), ", [F, A]),
255
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I)),
256
 
              io:format(Dev, "~n    or  ", []),
257
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I)),
258
 
              io:format(Dev, ", %lo(~w_~w), ", [F, A]),
259
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I));
260
 
            F -> 
261
 
              io:format(Dev, "    sethi %hi( ", []),
262
 
              io:format(Dev, "~w), ", [F]),
263
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I)),
264
 
              io:format(Dev, "~n    or  ", []),
265
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I)),
266
 
              io:format(Dev, ", %lo(~w), ", [F]),
267
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I))
268
 
          end;
269
 
        remote_function ->
270
 
          case Address of
271
 
            {M, F, A} -> 
272
 
              io:format(Dev, "    sethi %hi(~w_~w_~w), ", [M, F, A]),
273
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I)),
274
 
              io:format(Dev, "~n    or  ", []),
275
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I)),
276
 
              io:format(Dev, ", %lo(~w_~w_~w), ", [M, F, A]),
277
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I));
278
 
            {F, A} -> 
279
 
              io:format(Dev, "    sethi %hi(~w_~w), ", [F, A]),
280
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I)),
281
 
              io:format(Dev, "~n    or  ", []),
282
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I)),
283
 
              io:format(Dev, ", %lo(~w_~w), ", [F, A]),
284
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I));
285
 
            F -> 
286
 
              io:format(Dev, "    sethi %hi( ", []),
287
 
              io:format(Dev, "~w), ", [F]),
288
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I)),
289
 
              io:format(Dev, "~n    or  ", []),
290
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I)),
291
 
              io:format(Dev, ", %lo(~w), ", [F]),
292
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I))
293
 
          end;
294
 
        local_function ->
295
 
          case Address of
296
 
            {M, F, A} -> 
297
 
              io:format(Dev, "    sethi %hi(~w_~w_~w), ", [M, F, A]),
298
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I)),
299
 
              io:format(Dev, "~n    or  ", []),
300
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I)),
301
 
              io:format(Dev, ", %lo(~w_~w_~w), ", [M, F, A]),
302
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I));
303
 
            {F, A} -> 
304
 
              io:format(Dev, "    sethi %hi(~w_~w), ", [F, A]),
305
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I)),
306
 
              io:format(Dev, "~n    or  ", []),
307
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I)),
308
 
              io:format(Dev, ", %lo(~w_~w), ", [F, A]),
309
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I));
310
 
            F -> 
311
 
              io:format(Dev, "    sethi %hi( ", []),
312
 
              io:format(Dev, "~w), ", [F]),
313
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I)),
314
 
              io:format(Dev, "~n    or  ", []),
315
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I)),
316
 
              io:format(Dev, ", %lo(~w), ", [F]),
317
 
              pp_arg(Dev, hipe_sparc:load_address_dest(I))
318
 
          end;
319
 
        constant ->
320
 
          io:format(Dev, "    sethi %hi( ", []),
321
 
          io:format(Dev, "~s_dl_~w), ", [Pre, Address]),
322
 
          pp_arg(Dev, hipe_sparc:load_address_dest(I)),
323
 
          io:format(Dev, "~n    or  ", []),
324
 
          pp_arg(Dev, hipe_sparc:load_address_dest(I)),
325
 
          io:format(Dev, ", %lo(~s_dl_~w), ", [Pre, Address]),
326
 
          pp_arg(Dev, hipe_sparc:load_address_dest(I));
327
 
        c_const ->
328
 
          io:format(Dev, "    sethi %hi(", []),
329
 
          io:format(Dev, "~w), ", [Address]),
330
 
          pp_arg(Dev, hipe_sparc:load_address_dest(I)),
331
 
          io:format(Dev, "~n    or  ", []),
332
 
          pp_arg(Dev, hipe_sparc:load_address_dest(I)),
333
 
          io:format(Dev, ", %lo(~w), ", [Address]),
334
 
          pp_arg(Dev, hipe_sparc:load_address_dest(I));
335
 
        label ->
336
 
          io:format(Dev, "    sethi %hi( ", []),
337
 
          io:format(Dev, "~s_~w), ", [Pre, Address]),
338
 
          pp_arg(Dev, hipe_sparc:load_address_dest(I)),
339
 
          io:format(Dev, "~n    or", []),
340
 
          pp_arg(Dev, hipe_sparc:load_address_dest(I)),
341
 
          io:format(Dev, ", %lo(~s_dl_~w), ", [Pre, Address]),
342
 
          pp_arg(Dev, hipe_sparc:load_address_dest(I));
343
 
        closure ->
344
 
          io:format(Dev, "    lda ", []),
345
 
          io:format(Dev, "~s_~w, ", [Pre, Address]),
346
 
          pp_arg(Dev, hipe_sparc:load_address_dest(I)),
347
 
          io:format(Dev, " ! [closure]",[])
348
 
      end,
349
 
      io:format(Dev, "~n", []);
350
 
    #store{} ->
351
 
      io:format(Dev, "    ", []),
352
 
      pp_store_op(Dev, hipe_sparc:store_type(I)),
353
 
      io:format(Dev, " ", []),
354
 
      pp_arg(Dev, hipe_sparc:store_src(I)),
355
 
      io:format(Dev, ", [", []),
356
 
      pp_arg(Dev, hipe_sparc:store_dest(I)),
357
 
      io:format(Dev, "+", []),
358
 
      pp_arg(Dev, hipe_sparc:store_off(I)),
359
 
      io:format(Dev, "]~n", []);
360
 
    #rdy{} ->
361
 
      io:format(Dev, "    rd %y, ", []),
362
 
      pp_arg(Dev, hipe_sparc:rdy_dest(I)),
363
 
      io:format(Dev, "~n", []);
364
 
    #sethi{} ->
365
 
      io:format(Dev, "    sethi ", []),
366
 
      pp_arg(Dev, hipe_sparc:sethi_const(I)),
367
 
      io:format(Dev, ", ", []),
368
 
      pp_arg(Dev, hipe_sparc:sethi_dest(I)),
369
 
      io:format(Dev, "~n", []);
370
 
    #load_fp{} ->
371
 
      io:format(Dev, "    ", []),
372
 
      pp_load_fp_op(Dev, hipe_sparc:load_fp_type(I)),
373
 
      io:format(Dev, " [", []),
374
 
      pp_arg(Dev, hipe_sparc:load_fp_src(I)),
375
 
      io:format(Dev, "+", []),
376
 
      pp_arg(Dev, hipe_sparc:load_fp_off(I)),
377
 
      io:format(Dev, "], ", []),
378
 
      pp_arg(Dev, hipe_sparc:load_fp_dest(I)),
379
 
      io:format(Dev, "~n", []);
380
 
    #store_fp{} ->
381
 
      io:format(Dev, "    ", []),
382
 
      pp_store_fp_op(Dev, hipe_sparc:store_fp_type(I)),
383
 
      io:format(Dev, " ", []),
384
 
      pp_arg(Dev, hipe_sparc:store_fp_src(I)),
385
 
      io:format(Dev, ", [", []),
386
 
      pp_arg(Dev, hipe_sparc:store_fp_dest(I)),
387
 
      io:format(Dev, "+", []),
388
 
      pp_arg(Dev, hipe_sparc:store_fp_off(I)),
389
 
      io:format(Dev, "]~n", []);
390
 
%%  #fb{} ->
391
 
%%    io:format(Dev, "    fb", []),
392
 
%%    pp_fcc(Dev, hipe_sparc:fb_cond(I)),
393
 
%%    pp_annul(Dev, hipe_sparc:fb_annul(I)),
394
 
%%    pp_pred(Dev, hipe_sparc:fb_taken(I)),
395
 
%%    io:format(Dev, " %fcc~w",[hipe_sparc:fb_fcc_reg(I)]),
396
 
%%    pp_target(Dev, 
397
 
%%              hipe_sparc:fb_true_label(I),
398
 
%%              hipe_sparc:fb_false_label(I),
399
 
%%              Pre),
400
 
%%    io:format(Dev, "~n", []);
401
 
    #fop{} ->
402
 
      io:format(Dev, "    ", []),
403
 
      pp_fop_op(Dev, hipe_sparc:fop_operator(I)),
404
 
      pp_fp_type(Dev,hipe_sparc:fop_type(I)),
405
 
      io:format(Dev, " ", []),
406
 
      pp_arg(Dev, hipe_sparc:fop_src1(I)),
407
 
      io:format(Dev, ", ", []),
408
 
      pp_arg(Dev, hipe_sparc:fop_src2(I)),
409
 
      io:format(Dev, ", ", []),
410
 
      pp_arg(Dev, hipe_sparc:fop_dest(I)),
411
 
      io:format(Dev, "~n", []);
412
 
%%  #fcmp{} ->
413
 
%%    io:format(Dev, "    fcmp", []),
414
 
%%    case hipe_sparc:fcmp_exception(I) of
415
 
%%      true -> io:format(Dev, "e",[]);
416
 
%%      _ -> ok
417
 
%%    end,
418
 
%%    pp_fp_type(Dev,hipe_sparc:fcmp_type(I)),
419
 
%%    io:format(Dev, " ", []),
420
 
%%    io:format(Dev, " %fcc~w",[hipe_sparc:fcmp_fcc_reg(I)]),
421
 
%%    io:format(Dev, ",", []),
422
 
%%    pp_arg(Dev, hipe_sparc:fcmp_src1(I)),
423
 
%%    io:format(Dev, ", ", []),
424
 
%%    pp_arg(Dev, hipe_sparc:fcmp_src2(I)),
425
 
%%    io:format(Dev, "~n", []);
426
 
    #fmove{} ->
427
 
      case {hipe_sparc:fmove_negate(I),hipe_sparc:fmove_abs(I)} of
428
 
        {true, false} ->
429
 
          io:format(Dev, "    fneg", []);
430
 
        {false, true} ->
431
 
          io:format(Dev, "    fabs", []);
432
 
        {false, false} ->
433
 
          io:format(Dev, "    fmov", []);
434
 
        _ ->
435
 
          ?EXIT({"Illegal SPARC fmov instruction", I})
436
 
      end,
437
 
      pp_fp_type(Dev,hipe_sparc:fmove_type(I)),
438
 
      io:format(Dev, " ", []),
439
 
      pp_arg(Dev, hipe_sparc:fmove_src(I)),
440
 
      io:format(Dev, ", ", []),
441
 
      pp_arg(Dev, hipe_sparc:fmove_dest(I)),
442
 
      io:format(Dev, "~n", []);
443
 
    #conv_fp{} ->
444
 
      io:format(Dev, "    ", []),
445
 
      io:format(Dev, "fito", []),
446
 
      pp_fp_type(Dev, hipe_sparc:conv_fp_dest_type(I)),
447
 
      io:format(Dev, " ", []),
448
 
      pp_arg(Dev, hipe_sparc:conv_fp_src(I)),
449
 
      io:format(Dev, ", ", []),
450
 
      pp_arg(Dev, hipe_sparc:conv_fp_dest(I)),
451
 
      io:format(Dev, "~n", []);
452
 
    X ->
453
 
      ?EXIT({"unknown sparc instruction", X})
454
 
  end.
455
 
 
456
 
pp_mmoves(Dev, [Src|Srcs], [Dst| Dsts]) ->
457
 
  io:format(Dev, "    mov ", []),
458
 
  pp_arg(Dev, Src),
459
 
  io:format(Dev, ", ", []),
460
 
  pp_arg(Dev, Dst),
461
 
  io:format(Dev, " !~n", []),
462
 
  pp_mmoves(Dev, Srcs, Dsts);
463
 
pp_mmoves(_,[],[]) -> ok.
464
 
 
465
 
 
466
 
pp_alu_op(Dev, Op) ->
467
 
  Str = case Op of
468
 
          '+' -> "add";
469
 
          '-' -> "sub";
470
 
          '>>' -> "srl";
471
 
          '>>64' -> "srlx";
472
 
          '>>?' -> "sra";
473
 
          '>>?64' -> "srax";
474
 
          '<<' -> "sll";
475
 
          '<<64' -> "sllx";
476
 
          'and' -> "and";
477
 
          'or' -> "or";
478
 
          'xor' -> "xor";
479
 
          '+c' -> "addc";
480
 
          '-c' -> "subc";
481
 
          'andn' -> "andn";
482
 
          'xnor' ->  "xnor";
483
 
          'smul' -> "smul";
484
 
          X -> exit({sparc, {"unkown alu-op", X}}), ""
485
 
        end,
486
 
  io:format(Dev, "~s", [Str]).
487
 
 
488
 
pp_fop_op(Dev, Op) ->
489
 
  Str = case Op of
490
 
          '+' -> "fadd";
491
 
          '-' -> "fsub";
492
 
          '*' -> "fmul";
493
 
          '/' -> "fdiv";
494
 
          X -> exit({sparc, {"unkown floating point-op", X}}), ""
495
 
        end,
496
 
  io:format(Dev, "~s", [Str]).
497
 
 
498
 
pp_fp_type(Dev,Type) ->
499
 
  Str = case Type of
500
 
          single -> "s";
501
 
          double -> "d";
502
 
          quad -> "q"
503
 
        end,
504
 
  io:format(Dev, "~s", [Str]).
505
 
 
506
 
pp_load_fp_op(Dev, Type) ->
507
 
  Str = case Type of
508
 
          single -> "ld";
509
 
          double -> "ldd";
510
 
          quad -> "ldq"
511
 
        end,
512
 
  io:format(Dev, "~s", [Str]).
513
 
 
514
 
pp_store_fp_op(Dev, Type) ->
515
 
  Str = case Type of
516
 
          single -> "st";
517
 
          double -> "std";
518
 
          quad -> "stdq"
519
 
        end,
520
 
  io:format(Dev, "~s", [Str]).
521
 
 
522
 
pp_load_op(Dev, Type) ->
523
 
  Str = case Type of
524
 
          ub -> "ldub";
525
 
          sb -> "ldsb";
526
 
          uh -> "lduh";
527
 
          sh -> "ldsh";
528
 
          sw -> "ldsw";
529
 
          uw -> "lduw";
530
 
          xw -> "ldx"
531
 
        end,
532
 
  io:format(Dev, "~s", [Str]).
533
 
 
534
 
pp_store_op(Dev, Type) ->
535
 
  Str = case Type of
536
 
          b -> "stb";
537
 
          h -> "sth";
538
 
          w -> "stw";
539
 
          x -> "stx"
540
 
        end,
541
 
  io:format(Dev, "~s", [Str]).
542
 
 
543
 
 
544
 
%% pp_regcc(Dev, CC) ->
545
 
%%   io:format(Dev, "~s", [CC]).
546
 
 
547
 
pp_cc(Dev, CC) ->
548
 
  io:format(Dev, "~s", [CC]).
549
 
 
550
 
%% pp_fcc(Dev, FCC) ->
551
 
%%   io:format(Dev, "~s", [FCC]).
552
 
 
553
 
pp_arg(Dev, Arg) ->
554
 
  case  hipe_sparc:is_reg(Arg) of
555
 
    true ->
556
 
      io:format(Dev, "~s", 
557
 
                [hipe_sparc_registers:reg_name( hipe_sparc:reg_nr(Arg))]);
558
 
    false ->
559
 
      case hipe_sparc:is_imm(Arg) of
560
 
        true ->
561
 
          io:format(Dev, "~w", [ hipe_sparc:imm_value(Arg)]);
562
 
        false ->
563
 
          case hipe_sparc:is_fpreg(Arg) of
564
 
            true ->
565
 
              io:format(Dev, "~s", 
566
 
                        [hipe_sparc_registers:fpreg_name( hipe_sparc:fpreg_nr(Arg))]);
567
 
            false ->
568
 
              case hipe_sparc:is_spill(Arg) of
569
 
                true ->
570
 
                  io:format(Dev, "~w", [ hipe_sparc:spill_pos(Arg)]);
571
 
                false ->
572
 
                  ?EXIT({bad_sparc_arg,Arg})
573
 
              end
574
 
          end
575
 
      end
576
 
  end.
577
 
 
578
 
 
579
 
pp_args(_Dev, []) ->
580
 
  ok;
581
 
pp_args(Dev, [A]) ->
582
 
  pp_arg(Dev, A);
583
 
pp_args(Dev, [A|As]) ->
584
 
  pp_arg(Dev, A),
585
 
  io:format(Dev, ", ", []),
586
 
  pp_args(Dev, As).
587
 
 
588
 
 
589
 
pp_switch_labels(Dev,Lbls, Pre) -> 
590
 
  pp_switch_labels(Dev,Lbls,1, Pre).
591
 
 
592
 
pp_switch_labels(Dev, [L], _Pos, Pre) -> 
593
 
  io:format(Dev, "~s_~w", [Pre,L]);
594
 
pp_switch_labels(Dev, [L|Ls], Pos,Pre) -> 
595
 
  io:format(Dev, "~s_~w, ", [Pre,L]),
596
 
  NewPos = 
597
 
    case Pos of
598
 
      3 -> io:format(Dev, "\n             ! ",[]),
599
 
           0;
600
 
      N -> N + 1
601
 
    end,
602
 
  pp_switch_labels(Dev, Ls, NewPos, Pre);
603
 
pp_switch_labels(_Dev, [], _, _) -> ok.
604
 
 
605
 
 
606
 
pp_target(Dev,T,_Known=false) ->
607
 
  pp_arg(Dev,T);
608
 
pp_target(Dev,T,true) ->
609
 
  case T of
610
 
    {M, F, A} -> io:format(Dev, "~w_~w_~w ", [M, F, A]);
611
 
    {F, A} -> io:format(Dev, "~w_~w ", [F, A]);
612
 
    F -> io:format(Dev, "~w ", [F])
613
 
  end.
614
 
 
615
 
pp_target(Dev, Target, [], Pre) ->
616
 
  io:format(Dev, ", .~s_~w", [Pre, Target]);
617
 
pp_target(Dev, Target, Fail, Pre) ->
618
 
  io:format(Dev, ", .~s_~w ! .~s_~w", 
619
 
            [Pre, Target, Pre, Fail]). 
620
 
 
621
 
pp_annul(Dev, A) ->
622
 
  case A of
623
 
    a ->  io:format(Dev, ",a", []);
624
 
    na -> ok
625
 
  end.
626
 
 
627
 
 
628
 
pp_pred(Dev, P) ->
629
 
  case P of
630
 
    true -> ok;
631
 
    false -> io:format(Dev, ",pn", [])
632
 
  end.
633