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

« back to all changes in this revision

Viewing changes to lib/hipe/icode/hipe_icode_bincomp.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-07 15:07:37 UTC
  • mfrom: (1.2.1 upstream) (5.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090507150737-i4yb5elwinm7r0hc
Tags: 1:13.b-dfsg1-1
* Removed another bunch of non-free RFCs from original tarball
  (closes: #527053).
* Fixed build-dependencies list by adding missing comma. This requires
  libsctp-dev again. Also, added libsctp1 dependency to erlang-base and
  erlang-base-hipe packages because the shared library is loaded via
  dlopen now and cannot be added using dh_slibdeps (closes: #526682).
* Weakened dependency of erlang-webtool on erlang-observer to recommends
  to avoid circular dependencies (closes: #526627).
* Added solaris-i386 to HiPE enabled architectures.
* Made script sources in /usr/lib/erlang/erts-*/bin directory executable,
  which is more convenient if a user wants to create a target Erlang system.
* Shortened extended description line for erlang-dev package to make it
  fit 80x25 terminals.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%% -*- erlang-indent-level: 2 -*-
 
2
%%%
 
3
%%% %CopyrightBegin%
 
4
%%% 
 
5
%%% Copyright Ericsson AB 2006-2009. All Rights Reserved.
 
6
%%% 
 
7
%%% The contents of this file are subject to the Erlang Public License,
 
8
%%% Version 1.1, (the "License"); you may not use this file except in
 
9
%%% compliance with the License. You should have received a copy of the
 
10
%%% Erlang Public License along with this software. If not, it can be
 
11
%%% retrieved online at http://www.erlang.org/.
 
12
%%% 
 
13
%%% Software distributed under the License is distributed on an "AS IS"
 
14
%%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
15
%%% the License for the specific language governing rights and limitations
 
16
%%% under the License.
 
17
%%% 
 
18
%%% %CopyrightEnd%
 
19
%%%
2
20
%%%-------------------------------------------------------------------
3
21
%%% File    : hipe_icode_bincomp.erl
4
22
%%% Author  : Per Gustafsson <pergu@it.uu.se>
18
36
 
19
37
%%--------------------------------------------------------------------
20
38
 
21
 
-spec cfg(#cfg{}) -> #cfg{}.
 
39
-spec cfg(cfg()) -> cfg().
22
40
 
23
41
cfg(Cfg1) ->
24
 
  Start = hipe_icode_cfg:start_label(Cfg1),
25
 
  Cfg2 = find_bs_get_integer(ordsets:from_list([Start]), Cfg1,
26
 
                             ordsets:from_list([Start])),
27
 
  Cfg2.
 
42
  StartLbls = ordsets:from_list([hipe_icode_cfg:start_label(Cfg1)]),
 
43
  find_bs_get_integer(StartLbls, Cfg1, StartLbls).
28
44
 
29
45
find_bs_get_integer([Lbl|Rest], Cfg, Visited) ->
30
46
  BB = hipe_icode_cfg:bb(Cfg, Lbl),
38
54
       not_ok ->
39
55
         Cfg
40
56
     end,
41
 
  Succs = ordsets:from_list(hipe_icode_cfg:succ(NewCfg,Lbl)),
42
 
  NewSuccs = ordsets:subtract(Succs,Visited),
43
 
  NewLbls = ordsets:union(NewSuccs,Rest),
44
 
  NewVisited = ordsets:union(NewSuccs,Visited),
45
 
  find_bs_get_integer(NewLbls,NewCfg,NewVisited);
 
57
  Succs = ordsets:from_list(hipe_icode_cfg:succ(NewCfg, Lbl)),
 
58
  NewSuccs = ordsets:subtract(Succs, Visited),
 
59
  NewLbls = ordsets:union(NewSuccs, Rest),
 
60
  NewVisited = ordsets:union(NewSuccs, Visited),
 
61
  find_bs_get_integer(NewLbls, NewCfg, NewVisited);
46
62
find_bs_get_integer([], Cfg, _) ->
47
63
  Cfg.
48
64
 
52
68
      case hipe_icode:call_fun(I) of
53
69
        {hipe_bs_primop, {bs_get_integer, Size, Flags}} when (Flags band 6) =:= 0 ->
54
70
          case {hipe_icode:call_dstlist(I), hipe_icode:call_args(I)} of
55
 
            {[Dst,MsOut], [MsIn]} ->
 
71
            {[Dst, MsOut] = DstList, [MsIn]} ->
56
72
              Cont = hipe_icode:call_continuation(I),
57
73
              FirstFail = hipe_icode:call_fail_label(I),
58
74
              FirstFailBB = hipe_icode_cfg:bb(Cfg, FirstFail),
59
 
              case check_for_restore_block(FirstFailBB, [Dst, MsOut]) of
 
75
              case check_for_restore_block(FirstFailBB, DstList) of
60
76
                {restore_block, RealFail} ->
61
 
                  {ok, {{Dst,Size},FirstFail,RealFail,Cont,MsIn,MsOut}};
 
77
                  {ok, {{Dst, Size}, FirstFail, RealFail, Cont, MsIn, MsOut}};
62
78
                not_restore_block ->
63
79
                  not_ok
64
80
              end;
89
105
 
90
106
is_badinstr(Instr, DefVars) ->
91
107
  not(hipe_icode:is_move(Instr) andalso
92
 
      lists:member(hipe_icode:move_dst(Instr),DefVars)).
 
108
      lists:member(hipe_icode:move_dst(Instr), DefVars)).
93
109
 
94
110
collect_info(Lbl, Cfg, Acc, OldLbl, FailLbl, MsOut) ->
95
111
  case do_collect_info(Lbl, Cfg, Acc, FailLbl, MsOut) of