~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
2
2
%%
3
3
%% %CopyrightBegin%
4
4
%% 
5
 
%% Copyright Ericsson AB 2004-2009. All Rights Reserved.
 
5
%% Copyright Ericsson AB 2004-2011. All Rights Reserved.
6
6
%% 
7
7
%% The contents of this file are subject to the Erlang Public License,
8
8
%% Version 1.1, (the "License"); you may not use this file except in
93
93
-include("../ssa/hipe_ssa_const_prop.inc").
94
94
 
95
95
-type bool_lattice() :: 'true' | 'false' | 'top' | 'bottom'.
96
 
-type conditional()  :: 'eq' | 'ne' | 'ge' | 'geu' | 'gt' | 'gtu' | 'le'
97
 
                      | 'leu' | 'lt' | 'ltu' | 'overflow' | 'not_overflow'.
98
96
 
99
97
%%-----------------------------------------------------------------------------
100
98
%% Procedure : visit_expression/2
400
398
maybe_top_or_bottom([bottom | _], _) -> bottom;
401
399
maybe_top_or_bottom([_ | Rest],  TB) -> maybe_top_or_bottom(Rest, TB).
402
400
 
403
 
-spec partial_eval_branch(conditional(), bool_lattice(), bool_lattice(),
 
401
-spec partial_eval_branch(hipe_rtl:alub_cond(), bool_lattice(), bool_lattice(),
404
402
                          bool_lattice() | 0, bool_lattice() | 0) ->
405
403
         bool_lattice().
406
404
partial_eval_branch(Cond, N0, Z0, V0, C0) ->
441
439
                 hipe_rtl:alub_false_label(Inst)];
442
440
      top    -> [];
443
441
      _      ->
444
 
        %if the partial branch cannot be evaluated we must execute the 
445
 
        % instruction at runtime.
 
442
        %% if the partial branch cannot be evaluated we must execute the
 
443
        %% instruction at runtime.
446
444
        case partial_eval_branch(hipe_rtl:alub_cond(Inst), N, Z, C, V) of
447
445
          bottom -> [hipe_rtl:alub_true_label(Inst), 
448
446
                     hipe_rtl:alub_false_label(Inst)];
449
447
          top    -> [];
450
 
          true   -> [hipe_rtl:alub_true_label(Inst) ];
451
 
          false  -> [hipe_rtl:alub_false_label(Inst) ]
 
448
          true   -> [hipe_rtl:alub_true_label(Inst)];
 
449
          false  -> [hipe_rtl:alub_false_label(Inst)]
452
450
        end
453
451
     end,
454
452
  {[], NewSSA, NewEnv} = set_to(hipe_rtl:alub_dst(Inst), NewVal,  Env),
944
942
 
945
943
%% some small helpers.
946
944
alub_to_move(Inst, Res, Lab) ->
947
 
  [ hipe_rtl:mk_move(hipe_rtl:alub_dst(Inst), Res),
948
 
    hipe_rtl:mk_goto(Lab) ].
 
945
  [hipe_rtl:mk_move(hipe_rtl:alub_dst(Inst), Res),
 
946
   hipe_rtl:mk_goto(Lab)].
949
947
 
950
948
make_alub_subst_list(bottom, _, Tail) ->  Tail;
951
949
make_alub_subst_list(top, Src, _) ->
970
968
      %% move and the branch. We can however replace variable with constants:
971
969
      S1 = make_alub_subst_list(Val1, Src1, []),
972
970
      S2 = make_alub_subst_list(Val2, Src2, S1),
973
 
      [ hipe_rtl:subst_uses(S2, Inst) ];
974
 
    _ -> % we know where we will be going, let's find out what Dst should be.
975
 
         % knowing where we are going means that at most one of the values is
976
 
         % bottom, hence we can replace the alu-instr with a move. 
977
 
         % remember, a = b + 0 can give us enough info to know what jump to 
978
 
         % do without knowing the value of a. (I wonder if this will ever 
979
 
         % actualy happen ;) 
 
971
      [hipe_rtl:subst_uses(S2, Inst)];
 
972
    _ -> %% we know where we will be going, let's find out what Dst should be.
 
973
         %% knowing where we are going means that at most one of the values is
 
974
         %% bottom, hence we can replace the alu-instr with a move.
 
975
         %% remember, a = b + 0 can give us enough info to know what jump to
 
976
         %% do without knowing the value of a. (I wonder if this will ever
 
977
         %% actualy happen ;)
980
978
      Res = case ResVal of 
981
979
              bottom ->  % something nonconstant.
982
980
                if (Val1 =:= bottom) -> Src1;
985
983
              _ -> hipe_rtl:mk_imm(ResVal)
986
984
            end,
987
985
      case CondRes of 
988
 
        top -> io:format("oops. something VERY bad: ~w ~w V1 & 2 ~w ~w\n", 
989
 
                         [Inst, {ResVal, N, Z, C, V} , Val1, Val2]),
990
 
           [Inst ];
991
 
        true   -> alub_to_move(Inst, Res, hipe_rtl:alub_true_label(Inst));
992
 
        false  -> alub_to_move(Inst, Res, hipe_rtl:alub_false_label(Inst))
 
986
        top ->
 
987
          io:format("oops. something VERY bad: ~w ~w V1 & 2 ~w ~w\n",
 
988
                    [Inst, {ResVal, N, Z, C, V} , Val1, Val2]),
 
989
          [Inst];
 
990
        true  -> alub_to_move(Inst, Res, hipe_rtl:alub_true_label(Inst));
 
991
        false -> alub_to_move(Inst, Res, hipe_rtl:alub_false_label(Inst))
993
992
      end
994
993
  end.
995
994
 
1050
1049
 
1051
1050
%%-----------------------------------------------------------------------------
1052
1051
 
1053
 
%% make sure that all precoloured rgisters are taken out of the equation.
 
1052
%% make sure that all precoloured registers are taken out of the equation.
1054
1053
lookup_lattice_value(X, Environment) ->
1055
1054
  case hipe_rtl_arch:is_precoloured(X) or hipe_rtl:is_const_label(X) of 
1056
1055
    true ->