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

« back to all changes in this revision

Viewing changes to lib/hipe/rtl/hipe_rtl_arith_32.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) 2002 by Erik Johansson.  
3
 
%% -*- erlang-indent-level: 2 -*-
4
4
%% ====================================================================
5
5
%%  Filename :  hipe_rtl_arith_32.erl
6
6
%%  Module   :  hipe_rtl_arith_32
10
10
%%              of arithmetic on SPARC.
11
11
%%              XXX: This code is seldom used, and hence also
12
12
%%                   seldom tested. 
13
 
%%                   Look here for strange bugs appering when
 
13
%%                   Look here for strange bugs appearing when
14
14
%%                   turning on rtl_prop.
15
15
%%
16
16
%%  History  :  * 2002-10-23 Erik Stenman (happi@csd.uu.se): 
17
17
%%               Created.
18
18
%%  CVS      :
19
 
%%              $Author: pergu $
20
 
%%              $Date: 2003/04/23 11:58:14 $
21
 
%%              $Revision: 1.4 $
 
19
%%              $Author: kostis $
 
20
%%              $Date: 2004/04/30 06:58:44 $
 
21
%%              $Revision: 1.6 $
22
22
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
23
23
 
24
 
-include("../main/hipe.hrl").
25
 
 
26
24
-module(hipe_rtl_arith_32).
27
 
-export([eval_alu/3,eval_alub/4, eval_cond/3]).
 
25
-export([eval_alu/3, eval_alub/4, eval_cond/3, eval_cond_bits/5]).
28
26
 
29
 
-define(BITS,32).
30
 
-define(SIGN_BIT,31).
31
 
-define(WORDMASK,16#ffffffff).
32
 
-define(MAX_SIGNED_INT, 16#7fffffff).
33
 
-define(MIN_SIGNED_INT,-16#80000000).
 
27
-define(BITS, 32).
 
28
-define(SIGN_BIT, 31).
 
29
-define(WORDMASK,         16#ffffffff).
 
30
-define(MAX_SIGNED_INT,   16#7fffffff).
 
31
-define(MIN_SIGNED_INT,  -16#80000000).
34
32
-define(MAX_UNSIGNED_INT, 16#ffffffff).
35
33
 
36
 
 
37
 
 
38
 
%% Returns a tuple
39
 
%%  {Res, Sign, Zero, Overflow, Carry}
40
 
%%  Res will be a number in the range 
41
 
%%   MAX_SIGNED_INT >= Res >= MIN_SIGNED_INT
42
 
%% The other four values are flags that are either true or false
43
 
%% 
44
 
eval_alu(Op, Arg1, Arg2) 
45
 
  when Arg1 =< ?MAX_SIGNED_INT, 
46
 
       Arg1 >= ?MIN_SIGNED_INT,
47
 
       Arg2 =< ?MAX_SIGNED_INT, 
48
 
       Arg2 >= ?MIN_SIGNED_INT ->
49
 
 
50
 
  Sign1 = sign_bit(Arg1),
51
 
  Sign2 = sign_bit(Arg2),
52
 
 
53
 
  case Op of
54
 
    'sub' ->
55
 
      Res = (Arg1 - Arg2) band ?WORDMASK,
56
 
      N = sign_bit(Res),
57
 
      Z = zero(Res),
58
 
      V = (Sign1 and (not Sign2) and (not N)) 
59
 
        or
60
 
          ((not Sign1) and Sign2 and N),
61
 
      C = ((not Sign1) and Sign2) 
62
 
        or 
63
 
          (N and ((not Sign1) or Sign2));
64
 
  
65
 
    'add' ->
66
 
      Res = (Arg1 + Arg2) band ?WORDMASK,
67
 
      N = sign_bit(Res),
68
 
      Z = zero(Res),
69
 
      V = (Sign1 and Sign2 and (not N)) 
70
 
        or
71
 
          ((not Sign1) and (not Sign2) and N),
72
 
      C = (Sign1 and Sign2)
73
 
        or 
74
 
          ((not N) and (Sign1 or Sign2));
75
 
    'sra' ->
76
 
      Res = (Arg1 bsr Arg2) band ?WORDMASK,
77
 
      N = sign_bit(Res),
78
 
      Z = zero(Res),    
79
 
      V = 0,
80
 
      C = 0;
81
 
    'srl' ->
82
 
      Res = (Arg1 bsr Arg2) band shiftmask(Arg2),
83
 
      N = sign_bit(Res),
84
 
      Z = zero(Res),     
85
 
      V = 0,
86
 
      C = 0;
87
 
    'sll' ->
88
 
      Res = (Arg1 bsl Arg2) band ?WORDMASK, 
89
 
      N = sign_bit(Res),
90
 
      Z = zero(Res),     
91
 
      V = 0,
92
 
      C = 0;
93
 
    'or' ->
94
 
      Res = (Arg1 bor Arg2) band ?WORDMASK,
95
 
      N = sign_bit(Res),
96
 
      Z = zero(Res),     
97
 
      V = 0,
98
 
      C = 0;
99
 
    'and' ->
100
 
      Res =  (Arg1 band Arg2) band ?WORDMASK,
101
 
      N = sign_bit(Res),
102
 
      Z = zero(Res),     
103
 
      V = 0,
104
 
      C = 0;
105
 
    'xor' ->
106
 
      Res = (Arg1 bxor Arg2) band ?WORDMASK,
107
 
      N = sign_bit(Res),
108
 
      Z = zero(Res),     
109
 
      V = 0,
110
 
      C = 0;
111
 
    Op ->
112
 
      Res = N = Z = V = C = 0,
113
 
      ?EXIT({"unknown alu op", Op})
114
 
  end,
115
 
  {two_comp_to_erl(Res),N,Z,V,C};
116
 
eval_alu(Op,Arg1,Arg2) ->
117
 
  ?EXIT({argument_overflow,Op,Arg1,Arg2}).
118
 
  
119
 
 
120
 
eval_alub(Op, Cond, Arg1, Arg2) ->
121
 
  {Res,N,Z,V,C} = eval_alu(Op,Arg1,Arg2),
122
 
  case Cond of
123
 
    'eq' ->
124
 
      {Res, Z};
125
 
    'ne' -> 
126
 
      {Res, not Z};
127
 
    'gt'        -> 
128
 
      {Res, not (Z or (N xor V))};
129
 
    'gtu' -> 
130
 
      {Res, not (C or Z)};
131
 
    'ge' -> 
132
 
      {Res, not (N xor V)};
133
 
    'geu'-> 
134
 
      {Res, not C};
135
 
    'lt'        ->
136
 
      {Res, N xor V};
137
 
    'ltu'-> 
138
 
      {Res, C};
139
 
    'le'        ->
140
 
      {Res, Z or (N xor V)};
141
 
    'leu'-> 
142
 
      {Res, C or Z};
143
 
    'overflow' ->
144
 
      {Res,V};
145
 
    'not_overflow' ->
146
 
      {Res, not V};
147
 
    _ ->
148
 
      ?EXIT({'condition code not handled',Cond})
149
 
  end.
150
 
 
151
 
eval_cond(Cond, Arg1, Arg2) ->
152
 
  {_,Bool} = eval_alub('sub', Cond, Arg1, Arg2),
153
 
  Bool.
154
 
 
155
 
 
156
 
sign_bit(Val) ->
157
 
  ((Val bsr ?SIGN_BIT) band 1) =:= 1.
158
 
two_comp_to_erl(V) ->
159
 
  if V > ?MAX_SIGNED_INT ->
160
 
      - ((?MAX_UNSIGNED_INT + 1) - V);
161
 
     true -> V
162
 
  end.
163
 
 
164
 
shiftmask(Arg) ->
165
 
  Setbits=32-Arg,
166
 
  round(math:pow(2,Setbits)-1).
167
 
 
168
 
zero(Val) ->
169
 
  Val =:= 0.
170
 
 
 
34
-include("../main/hipe.hrl").    %% for ?EXIT
 
35
 
 
36
-include("hipe_rtl_arith.inc").