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

« back to all changes in this revision

Viewing changes to lib/hipe/arm/hipe_rtl_to_arm.erl

  • Committer: Bazaar Package Importer
  • Author(s): Soren Hansen
  • Date: 2007-05-01 16:57:10 UTC
  • mfrom: (1.1.9 upstream)
  • Revision ID: james.westby@ubuntu.com-20070501165710-2sapk0hp2gf3o0ip
Tags: 1:11.b.4-2ubuntu1
* Merge with Debian Unstable. Remaining changes:
  - Add -fno-stack-protector to fix broken crypto_drv.
* DebianMaintainerField update.

Show diffs side-by-side

added added

removed removed

Lines of Context:
81
81
  case RtlAluOp of
82
82
    'add' -> 'add';
83
83
    'sub' -> 'sub';
 
84
    'mul' -> 'mul';
84
85
    'or'  -> 'orr';
85
86
    'and' -> 'and';
86
87
    'xor' -> 'eor'
168
169
  mk_arith_ri(S, Dst, Src2, commute_arithop(ArithOp), Src1).
169
170
 
170
171
mk_arith_ri(S, Dst, Src1, ArithOp, Src2) ->
171
 
  {FixAm1,NewArithOp,Am1} = fix_aluop_imm(ArithOp, Src2),
172
 
  FixAm1 ++ [hipe_arm:mk_alu(NewArithOp, S, Dst, Src1, Am1)].
 
172
  case ArithOp of
 
173
    'mul' -> % mul/smull only take reg/reg operands
 
174
      Tmp = new_untagged_temp(),
 
175
      mk_li(Tmp, Src2,
 
176
            mk_arith_rr(S, Dst, Src1, ArithOp, Tmp));
 
177
    _ -> % add/sub/orr/and/eor have reg/am1 operands
 
178
      {FixAm1,NewArithOp,Am1} = fix_aluop_imm(ArithOp, Src2),
 
179
      FixAm1 ++ [hipe_arm:mk_alu(NewArithOp, S, Dst, Src1, Am1)]
 
180
  end.
173
181
 
174
182
mk_arith_rr(S, Dst, Src1, ArithOp, Src2) ->
175
 
  [hipe_arm:mk_alu(ArithOp, S, Dst, Src1, Src2)].
 
183
  case {ArithOp,S} of
 
184
    {'mul',true} ->
 
185
      %% To check for overflow in 32x32->32 multiplication:
 
186
      %% smull Dst,TmpHi,Src1,Src2
 
187
      %% mov TmpSign,Dst,ASR #31
 
188
      %% cmp TmpSign,TmpHi
 
189
      %% [bne OverflowLabel]
 
190
      TmpHi = new_untagged_temp(),
 
191
      TmpSign = new_untagged_temp(),
 
192
      [hipe_arm:mk_smull(Dst, TmpHi, Src1, Src2),
 
193
       hipe_arm:mk_move(TmpSign, {Dst,'asr',31}),
 
194
       hipe_arm:mk_cmp('cmp', TmpSign, TmpHi)];
 
195
    _ ->
 
196
      [hipe_arm:mk_alu(ArithOp, S, Dst, Src1, Src2)]
 
197
  end.
176
198
 
177
199
fix_aluop_imm(AluOp, Imm) -> % {FixAm1,NewAluOp,Am1}
178
200
  case hipe_arm:try_aluop_imm(AluOp, Imm) of
187
209
  {Dst, Map0} = conv_dst(hipe_rtl:alub_dst(I), Map),
188
210
  {Src1, Map1} = conv_src(hipe_rtl:alub_src1(I), Map0),
189
211
  {Src2, Map2} = conv_src(hipe_rtl:alub_src2(I), Map1),
190
 
  Cond = conv_alub_cond(hipe_rtl:alub_cond(I)),
 
212
  RtlAluOp = hipe_rtl:alub_op(I),
 
213
  Cond0 = conv_alub_cond(hipe_rtl:alub_cond(I)),
 
214
  Cond =
 
215
    case {RtlAluOp,Cond0} of
 
216
      {'mul','vs'} -> 'ne';     % overflow becomes not-equal
 
217
      {'mul','vc'} -> 'eq';     % no-overflow becomes equal
 
218
      {'mul',_} -> exit({?MODULE,I});
 
219
      {_,_} -> Cond0
 
220
    end,
191
221
  I2 = mk_pseudo_bc(
192
222
          Cond,
193
223
          hipe_rtl:alub_true_label(I),
194
224
          hipe_rtl:alub_false_label(I),
195
225
          hipe_rtl:alub_pred(I)),
196
 
  RtlAluOp = hipe_rtl:alub_op(I),
197
226
  S = true,
198
227
  I1 = mk_alu(S, Dst, Src1, RtlAluOp, Src2),
199
228
  {I1 ++ I2, Map2, Data}.
453
482
     true ->
454
483
      Index = new_untagged_temp(),
455
484
      Am3 = hipe_arm:mk_am3(Base, Sign, Index),
456
 
      [mk_li(Index, AbsOffset),
457
 
       hipe_arm:mk_ldrsb(Dst, Am3)]
 
485
      mk_li(Index, AbsOffset,
 
486
            [hipe_arm:mk_ldrsb(Dst, Am3)])
458
487
  end.
459
488
 
460
489
mk_ldrsb_rr(Dst, Base1, Base2) ->