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

« back to all changes in this revision

Viewing changes to lib/hipe/sparc/hipe_sparc_verify.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
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2
 
%% Copyright (c) 2001 by Erik Johansson.  All Rights Reserved 
3
 
%% -*- erlang-indent-level: 2 -*-
4
 
%% ====================================================================
5
 
%%  Filename :  hipe_sparc_verify.erl
6
 
%%  Module   :  hipe_sparc_verify
7
 
%%  Purpose  :  
8
 
%%  Notes    : 
9
 
%%  History  :  * 2001-10-25 Erik Johansson (happi@csd.uu.se): 
10
 
%%               Created.
11
 
%%  CVS      :
12
 
%%              $Author: richardc $
13
 
%%              $Date: 2002/10/01 12:47:17 $
14
 
%%              $Revision: 1.2 $
15
 
%% ====================================================================
16
 
%%  Exports  :
17
 
%%
18
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
19
 
 
20
 
-module(hipe_sparc_verify).
21
 
-export([verify/2]).
22
 
 
23
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
24
 
%%
25
 
%% Verifies that a code sequence is well-formed.
26
 
%%
27
 
%% NOTE: does not consider branch offsets.
28
 
 
29
 
verify([],Version) -> ok;
30
 
verify([X|Xs],Version) ->
31
 
  case catch ver(X,Version) of
32
 
    {'EXIT',_} ->
33
 
      report('instruction ~w malformed~n',[X]);
34
 
    _ -> ok
35
 
  end,
36
 
  verify(Xs,Version).
37
 
 
38
 
ver(Label,_Version) when is_record(Label,label) ->
39
 
  L = Label#label.id,
40
 
  if
41
 
    is_integer(L), L > 0 -> ok
42
 
  end;
43
 
 
44
 
ver(Nop,_Version) when is_record(Nop,nop) -> 
45
 
  ok;
46
 
ver(Comment,_Version) when is_record(Comment,comment) -> 
47
 
  ok;
48
 
ver(Align,_Version) when is_record(Align,align) ->
49
 
  N = Align#align.alignment,
50
 
  if
51
 
    N == 1 -> ok;
52
 
    N == 2 -> ok;
53
 
    N == 4 -> ok;
54
 
    N == 8 -> ok;
55
 
    N == 16 -> ok
56
 
  end;
57
 
ver(Move,_Version) when is_record(Move,move) ->
58
 
  Dst = Move#move.dst,
59
 
  Src = Move#move.src,
60
 
  case {reg(Dst),reg_or_imm13(Src)} of
61
 
    {true,true} -> ok
62
 
  end;
63
 
ver(Cmov_cc,Version) when is_record(Cmov_cc,cmov_cc) ->
64
 
  if 
65
 
    Version == 9 ->
66
 
      Dst = Cmov_cc#cmov_cc.dst,
67
 
      Src = Cmov_cc#cmov_cc.src,
68
 
      CC = Cmov_cc#cmov_cc.cc,
69
 
      case {reg(Dst),reg_or_imm11(Src),int_cc(CC)} of
70
 
        {true,true,true} -> ok
71
 
      end
72
 
  end;
73
 
ver(Cmov_r,Version) when is_record(Cmov_r,cmov_r) ->
74
 
  if 
75
 
    Version == 9 ->
76
 
      Dst = Cmov_r#cmov_r.dst,
77
 
      Src = Cmov_r#cmov_r.src,
78
 
      Pred = Cmov_r#cmov_r.reg,
79
 
      Cond = Cmov_r#cmov_r.rcc,
80
 
      case {reg(Dst),reg_or_imm10(Src),reg(Pred),reg_cc(Cond)} of
81
 
        {true,true,true,true} -> ok
82
 
      end
83
 
  end;
84
 
ver(Alu,Version) when is_record(Alu,alu) ->
85
 
  Dst = Alu#alu.dst,
86
 
  Src1 = Alu#alu.src1,
87
 
  Op = Alu#alu.op,
88
 
  Src2 = Alu#alu.src2,
89
 
  case {reg(Dst),reg(Src1),alu_op(Op,Version),reg_or_imm13(Src2)} of
90
 
    {true,true,true,true} ->
91
 
      ok
92
 
  end;
93
 
ver(Alu_cc,Version) when is_record(Alu_cc,alu_cc) ->
94
 
  Dst = Alu_cc#alu_cc.dst,
95
 
  Src1 = Alu_cc#alu_cc.src1,
96
 
  Op = Alu_cc#alu_cc.op,
97
 
  Src2 = Alu_cc#alu_cc.src2,
98
 
  case {reg(Dst),reg(Src1),alu_cc_op(Op,Version),reg_or_imm13(Src2)} of
99
 
    {true,true,true,true} -> ok
100
 
  end;
101
 
ver(Sethi,_Version) when is_record(Sethi,sethi) ->
102
 
  Dst = Sethi#sethi.dst,
103
 
  Const = Sethi#sethi.const,
104
 
  case {reg(Dst),imm22(Const)} of
105
 
    {true,true} -> ok
106
 
  end;
107
 
ver(Load,_Version) when is_record(Load,load) ->
108
 
  Dst = Load#load.dst,
109
 
  Type = Load#load.type,
110
 
  Src = Load#load.src,
111
 
  Off = Load#load.off,
112
 
  case {reg(Dst),loading_type(Type),reg(Src),reg_or_imm13(Off)} of
113
 
    {true,true,true,true} -> ok
114
 
  end;
115
 
ver(Store,_Version) when is_record(Store,store) ->
116
 
  Dst = Store#store.dst,
117
 
  Off = Store#store.off,
118
 
  Type = Store#store.type,
119
 
  Src = Store#store.src,
120
 
  case {reg(Dst),reg_or_imm13(Off),storing_type(Type),reg(Src)} of
121
 
    {true,true,true,true} -> ok
122
 
  end;
123
 
ver(B,Version) when is_record(B,b) ->
124
 
  CC = B#b.cc,
125
 
  Pred = B#b.pred,
126
 
  Annul = B#b.annul,
127
 
  if
128
 
    Version == 9 ->
129
 
      case {int_cc(CC),prediction(Pred),annul_info(Annul)} of
130
 
        {true,true,true} -> ok
131
 
      end;
132
 
    Version == 8 ->
133
 
      case {int_cc(CC),prediction(Pred),annul_info(Annul)} of
134
 
        {true,true,true} -> ok
135
 
      end
136
 
  end;
137
 
ver(Br,Version) when is_record(Br,br) ->
138
 
  Reg = Br#br.reg,
139
 
  RC = Br#br.rcc,
140
 
  Pred = Br#br.pred,
141
 
  Annul = Br#br.annul,
142
 
  if
143
 
    Version == 9 ->
144
 
      case {reg(Reg),reg_cc(RC),prediction(Pred),annul_info(Annul)} of
145
 
        {true,true,true,true} -> ok
146
 
      end
147
 
  end;
148
 
ver(Jmp_link,_Version) when is_record(Jmp_link,jmp_link) ->
149
 
  Target = Jmp_link#jmp_link.target,
150
 
  Off = Jmp_link#jmp_link.off,
151
 
  Link = Jmp_link#jmp_link.link,
152
 
  case {reg(Target),reg_or_imm13(Off),reg(Link)} of
153
 
    {true,true,true} -> ok
154
 
  end;
155
 
ver(Jmp,_Version) when is_record(Jmp,jmp) ->
156
 
  Target = Jmp#jmp.target,
157
 
  Off = Jmp#jmp.off,
158
 
  case {reg(Target),reg_or_imm13(Off)} of
159
 
    {true,true} -> ok
160
 
  end;
161
 
ver(Call_link,_Version) when is_record(Call_link,call_link) ->
162
 
  Link = Call_link#call_link.link,
163
 
  case reg(Link) of
164
 
    true -> ok
165
 
  end.
166
 
 
167
 
 
168
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
169
 
                                                %
170
 
                                                % Condition code handling.
171
 
                                                %
172
 
 
173
 
reg_cc(RCond) ->        % for BPr and CMOVr isns
174
 
  case RCond of
175
 
    'z' -> true;
176
 
    'lez'       -> true;
177
 
    'lz'        -> true;
178
 
    'nz'        -> true;
179
 
    'gz'        -> true;
180
 
    'gez'       -> true;
181
 
    _   -> false        % XXX: serious error, should exit
182
 
  end.
183
 
 
184
 
int_cc(Cond) ->
185
 
  case Cond of
186
 
    'a' -> true;
187
 
    'n' -> true;
188
 
    'ne'        -> true;
189
 
    'e' -> true;
190
 
    'g' -> true;
191
 
    'le'        -> true;
192
 
    'ge'        -> true;
193
 
    'l' -> true;
194
 
    'gu'        -> true;
195
 
    'leu'       -> true;
196
 
    'geu'       -> true;
197
 
    'lu'        -> true;
198
 
    'pos'       -> true;
199
 
    'neg'       -> true;
200
 
    'vc'        -> true;
201
 
    'vs'        -> true;
202
 
    _   -> false        % XXX: serious error, should exit
203
 
  end.
204
 
 
205
 
 
206
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
207
 
 
208
 
reg({reg,R}) when is_integer(R), R >= 0 -> true;
209
 
reg(_) -> false.
210
 
 
211
 
reg_or_imm13({imm,Imm}) ->
212
 
  imm13(Imm);
213
 
reg_or_imm13(Reg) -> reg(Reg).
214
 
 
215
 
reg_or_imm11({imm,Imm}) ->
216
 
  imm11(Imm);
217
 
reg_or_imm11(Reg) -> reg(Reg).
218
 
 
219
 
reg_or_imm10({imm,Imm}) ->
220
 
  imm10(Imm);
221
 
reg_or_imm10(Reg) -> reg(Reg).
222
 
 
223
 
                                                % Note: does not verify branch offsets
224
 
 
225
 
                                                %label_imm16({label,L}) when L > 0 -> true;  
226
 
                                                %label_imm16(_) -> false.
227
 
 
228
 
                                                %label_imm19({label,L}) when L > 0 -> true;
229
 
                                                %label_imm19(_) -> false.
230
 
 
231
 
                                                %label_imm22({label,L}) when L > 0 -> true;
232
 
                                                %label_imm22(_) -> false.
233
 
 
234
 
                                                %label_imm30({label,L}) when L > 0 -> true;
235
 
                                                %label_imm30(_) -> false.
236
 
 
237
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
238
 
 
239
 
imm10(N) -> imm(N,10).
240
 
imm11(N) -> imm(N,11).
241
 
imm13(N) -> imm(N,13).
242
 
%imm16(N) -> imm(N,16).
243
 
%imm19(N) -> imm(N,19).
244
 
imm22(N) -> imm(N,22).
245
 
 
246
 
imm(Imm,N) when Imm >= -((1 bsl N+1)-1), Imm < (1 bsl N+1) ->
247
 
  true;
248
 
imm(Imm,N) ->
249
 
  false.
250
 
 
251
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
252
 
 
253
 
prediction(taken) -> true;
254
 
prediction(untaken) -> true;
255
 
prediction(_) -> false.
256
 
 
257
 
annul_info(a) -> true;
258
 
annul_info(na) -> true;
259
 
annul_info(_) -> false.
260
 
 
261
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
262
 
 
263
 
loading_type(X) -> data_type(X).
264
 
 
265
 
storing_type(X) -> data_type(X).
266
 
 
267
 
data_type(sb) -> true;
268
 
data_type(sh) -> true;
269
 
data_type(sw) -> true;
270
 
data_type(ub) -> true;
271
 
data_type(uh) -> true;
272
 
data_type(uw) -> true;
273
 
data_type(xw) -> true;
274
 
data_type(_) -> false.
275
 
 
276
 
alu_op(X,Version) -> int_op(X,Version).
277
 
 
278
 
alu_cc_op(X,Version) -> int_op(X,Version).
279
 
 
280
 
int_op('+',Version) -> is_version(Version,[8,9]);
281
 
int_op('+c',Version) -> is_version(Version,[8,9]);
282
 
int_op('and',Version) -> is_version(Version,[8,9]);
283
 
int_op('andn',Version) -> is_version(Version,[8,9]);
284
 
int_op('or',Version) -> is_version(Version,[8,9]);
285
 
int_op('orn',Version) -> is_version(Version,[8,9]);
286
 
int_op('xor',Version) -> is_version(Version,[8,9]);
287
 
int_op('xnor',Version) -> is_version(Version,[8,9]);
288
 
int_op('-',Version) -> is_version(Version,[8,9]);
289
 
int_op('-c',Version) -> is_version(Version,[8,9]);
290
 
int_op('<<',Version) -> is_version(Version,[8,9]);
291
 
int_op('>>',Version) -> is_version(Version,[8,9]);
292
 
int_op('>>?',Version) -> is_version(Version,[8,9]);
293
 
int_op('*s',Version) -> is_version(Version,[8,9]);
294
 
int_op('*u',Version) -> is_version(Version,[8,9]);
295
 
int_op('/s',Version) -> is_version(Version,[8,9]);
296
 
int_op('/u',Version) -> is_version(Version,[8,9]);
297
 
int_op('<<64',Version) -> is_version(Version,9);
298
 
int_op('>>64',Version) -> is_version(Version,9);
299
 
int_op('>>?64',Version) -> is_version(Version,9);
300
 
int_op('*64',Version) -> is_version(Version,9);
301
 
int_op('/s64',Version) -> is_version(Version,9);
302
 
int_op('/u64',Version) -> is_version(Version,9);
303
 
int_op(_,_) -> false.
304
 
 
305
 
is_version(Version,Version) -> true;
306
 
is_version(Version,VersionList) -> member(Version,VersionList).
307
 
 
308
 
member(Version,[Version|_]) -> true;
309
 
member(Version,[_|Versions]) -> member(Version,Versions);
310
 
member(_,[]) -> false.
311
 
 
312
 
 
313
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
314
 
 
315
 
report(String,Args) -> io:format(String,Args), io:format('~n',[]).
316
 
 
317