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

« back to all changes in this revision

Viewing changes to lib/hipe/rtl/hipe_rtl_ssapre.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-08-05 20:54:29 UTC
  • mfrom: (6.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090805205429-pm4pnwew8axraosl
Tags: 1:13.b.1-dfsg-5
* Fixed parentheses in Emacs mode (closes: #536891).
* Removed unnecessary conflicts with erlang-manpages package.
* Added workaround for #475459: disabled threads on sparc architecture.
  This breaks wxErlang, so it's only a temporary solution.

Show diffs side-by-side

added added

removed removed

Lines of Context:
400
400
              false -> Expr
401
401
            end,
402
402
  SRC2 = ?RTL:alu_src2(NewExpr),
403
 
  NewExpr2 = case SRC2 =:= S of
404
 
               true  -> ?RTL:alu_src2_update(NewExpr,Var);
405
 
               false -> NewExpr
406
 
             end,
407
 
  NewExpr2.
 
403
  case SRC2 =:= S of
 
404
    true  -> ?RTL:alu_src2_update(NewExpr,Var);
 
405
    false -> NewExpr
 
406
  end.
408
407
 
409
408
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
410
409
 
1230
1229
              #temp{} -> ?RTL:alu_src1_update(Expr,S1#temp.var);
1231
1230
              _ -> Expr
1232
1231
            end,
1233
 
  NewExpr = case S2 of
1234
 
              #temp{} -> ?RTL:alu_src2_update(NewInst,S2#temp.var);
1235
 
              _ -> NewInst
1236
 
            end,
1237
 
  NewExpr.
 
1232
  case S2 of
 
1233
    #temp{} -> ?RTL:alu_src2_update(NewInst,S2#temp.var);
 
1234
    _ -> NewInst
 
1235
  end.
1238
1236
 
1239
1237
get_insertions([],OpAcc,InsertionsAcc,_Visited,_Expr,_XsiG) ->
1240
1238
  {OpAcc,InsertionsAcc};
1246
1244
      case gb_trees:lookup(Pred,InsertionsAcc) of
1247
1245
        {value,Insertion} ->
1248
1246
          From = Insertion#insertion.from,
1249
 
          case lists:keysearch(Op,1,From) of
1250
 
            false -> 
 
1247
          case lists:keyfind(Op, 1, From) of
 
1248
            false ->
1251
1249
              ?pp_debug("~nThere has been insertions along the edge L~w already, but not for that operand | Op=",[Pred]),pp_arg(Op),
1252
1250
              Dst = Op#bottom.var,
1253
1251
              Expr2 = ?RTL:alu_dst_update(Expr,Dst),
1255
1253
              Code = Insertion#insertion.code,
1256
1254
              NewInsertion = Insertion#insertion{from=[{Op,Dst}|From],code=[Inst|Code]},
1257
1255
              NewInsertionsAcc = gb_trees:update(Pred,NewInsertion,InsertionsAcc);
1258
 
            {value,{_,Val}} ->
 
1256
            {_, Val} ->
1259
1257
              ?pp_debug("~nThere has been insertions along the edge L~w already, and for that operand too | Op=",[Pred]),pp_arg(Op),
1260
1258
              Dst = Val,
1261
1259
              NewInsertionsAcc = InsertionsAcc
1272
1270
      case gb_trees:lookup(Pred,InsertionsAcc) of
1273
1271
        {value,Insertion} ->
1274
1272
          From = Insertion#insertion.from,
1275
 
          case lists:keysearch(Op,1,From) of
1276
 
            false -> 
 
1273
          case lists:keyfind(Op, 1, From) of
 
1274
            false ->
1277
1275
              ?pp_debug("~nThere have been insertions along the edge L~w already, but not for that operand | Op=",[Pred]),pp_arg(Op),
1278
1276
              Dst = Op#const_expr.var,
1279
1277
              Val = Op#const_expr.value,
1281
1279
              Code = Insertion#insertion.code,
1282
1280
              NewInsertion = Insertion#insertion{from=[{Op,Dst}|From],code=[Inst|Code]},
1283
1281
              NewInsertionsAcc = gb_trees:update(Pred,NewInsertion,InsertionsAcc);
1284
 
            {value,{_,Val}} ->
 
1282
            {_, Val} ->
1285
1283
              ?pp_debug("~nThere have been insertions along the edge L~w already, and for that operand too | Op=",[Pred]),pp_arg(Op),
1286
1284
              Dst = Val,
1287
1285
              NewInsertionsAcc = InsertionsAcc
1300
1298
      case gb_trees:lookup(Pred,InsertionsAcc) of
1301
1299
        {value,Insertion} ->
1302
1300
          From = Insertion#insertion.from,
1303
 
          case lists:keysearch(Op,1,From) of
1304
 
            false -> 
 
1301
          case lists:keyfind(Op, 1, From) of
 
1302
            false ->
1305
1303
              ?pp_debug("~nThere has been insertions along the edge L~w already, but not for that operand | Op=",[Pred]),pp_arg(Op),
1306
1304
              Dst = Op#eop.var,
1307
1305
              Expr2 = ?RTL:alu_dst_update(Expr,Dst),
1309
1307
              Code = Insertion#insertion.code,
1310
1308
              NewInsertion = Insertion#insertion{from=[{Op,Dst}|From],code=[Inst|Code]},
1311
1309
              NewInsertionsAcc = gb_trees:update(Pred,NewInsertion,InsertionsAcc);
1312
 
            {value,{_,Val}} ->
 
1310
            {_, Val} ->
1313
1311
              ?pp_debug("~nThere has been insertions along the edge L~w already, and for that operand too | Op=",[Pred]),pp_arg(Op),
1314
1312
              Dst = Val,
1315
1313
              NewInsertionsAcc = InsertionsAcc
1326
1324
      case gb_trees:lookup(Pred,InsertionsAcc) of
1327
1325
        {value,Insertion} ->
1328
1326
          From = Insertion#insertion.from,
1329
 
          case lists:keysearch(Op,1,From) of
1330
 
            false -> 
 
1327
          case lists:keyfind(Op, 1, From) of
 
1328
            false ->
1331
1329
              ?pp_debug("~nThere has been insertions along the edge L~w already, but not for that operand | Op=",[Pred]),pp_arg(Op),
1332
1330
              Key = Op#temp.key,
1333
1331
              {_V,Xsi} = ?GRAPH:vertex(XsiG,Key),      
1345
1343
                  NewInsertion = Insertion#insertion{from=[{Op,Dst}|From],code=[Inst|Code]},
1346
1344
                  NewInsertionsAcc = gb_trees:update(Pred,NewInsertion,InsertionsAcc)
1347
1345
              end;
1348
 
            {value,{_,Val}} ->
 
1346
            {_, Val} ->
1349
1347
              ?pp_debug("~nThere has been insertions along the edge L~w already, and for that operand too (Op=~w)",[Pred,Op]),
1350
1348
              ?pp_debug("~nThis means, this temp is a WBA Xsi's definition",[]),
1351
1349
              Dst = Val,
1420
1418
xsi_oplist(#xsi{opList=OpList}) ->
1421
1419
  case OpList of undefined -> [] ; _ -> OpList end.
1422
1420
xsi_arg(Xsi, Pred) ->
1423
 
  case lists:keysearch(Pred, #xsi_op.pred ,xsi_oplist(Xsi)) of
 
1421
  case lists:keyfind(Pred, #xsi_op.pred, xsi_oplist(Xsi)) of
1424
1422
    false ->
1425
1423
      undetermined_operand;
1426
 
    {value,R} ->
 
1424
    R ->
1427
1425
      R#xsi_op.op
1428
1426
  end.
1429
1427
xsi_arg_update(Xsi, Pred, Op) ->