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

« back to all changes in this revision

Viewing changes to lib/hipe/x86/hipe_x86_spill_restore.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:
1
1
%% -*- erlang-indent-level: 2 -*-
2
2
%%
3
3
%% %CopyrightBegin%
4
 
%% 
5
 
%% Copyright Ericsson AB 2008-2009. All Rights Reserved.
6
 
%% 
 
4
%%
 
5
%% Copyright Ericsson AB 2008-2010. All Rights Reserved.
 
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
9
9
%% compliance with the License. You should have received a copy of the
10
10
%% Erlang Public License along with this software. If not, it can be
11
11
%% retrieved online at http://www.erlang.org/.
12
 
%% 
 
12
%%
13
13
%% Software distributed under the License is distributed on an "AS IS"
14
14
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
15
15
%% the License for the specific language governing rights and limitations
16
16
%% under the License.
17
 
%% 
 
17
%%
18
18
%% %CopyrightEnd%
19
19
%%
20
20
%% ====================================================================
71
71
  case hipe_x86_cfg:reverse_postorder(CFG0) of
72
72
    [Label1, Label2|_] ->
73
73
      SaveTreeElement = saveTreeLookup(Label2, SaveTree),
74
 
      %% FilteredSaveTreeElement is the to be spilled temps around the function call. 
75
 
      %% They are spilled just before move formals
76
 
      FilteredSaveTreeElement = [Temp || Temp <- SaveTreeElement, temp_is_pseudo(Temp)],
 
74
      %% FilteredSaveTreeElement is the to be spilled temps around the
 
75
      %% function call. They are spilled just before move formals.
 
76
      FilteredSaveTreeElement = [T || T <- SaveTreeElement, temp_is_pseudo(T)],
77
77
      Block = hipe_x86_cfg:bb(CFG1, Label1),
78
78
      Code = hipe_bb:code(Block),
79
79
      %% The following statements are tedious but work ok.
83
83
      %% Another solution may be to introduce another block.
84
84
      MoveCodes = lists:sublist(Code, length(Code)-1),
85
85
      JumpCode = lists:last(Code),
86
 
      hipe_x86_cfg:bb_add(CFG1, Label1, hipe_bb:mk_bb(MoveCodes ++ [hipe_x86:mk_pseudo_spill(FilteredSaveTreeElement)] ++ [JumpCode]));
 
86
      hipe_x86_cfg:bb_add(CFG1, Label1, hipe_bb:mk_bb(MoveCodes ++ [hipe_x86:mk_pseudo_spill(FilteredSaveTreeElement), JumpCode]));
87
87
    _ ->
88
88
      CFG1
89
89
  end.
110
110
  NewBlock = hipe_bb:code_update(Block, NewCode),
111
111
  NewCFG = hipe_x86_cfg:bb_add(CFG, Label, NewBlock), 
112
112
  SizeOfSet = setSize(NewIntersectedList),
113
 
  
114
113
  %% if the Intersected Save List is not empty, insert it in the save tree.
115
114
  if SizeOfSet =/= 0 ->
116
 
      UpdatedSaveTree = gb_trees:insert(Label,NewIntersectedList,SaveTree),
117
 
      firstPassHelper(Labels, Liveness, NewCFG,UpdatedSaveTree);
 
115
      UpdatedSaveTree = gb_trees:insert(Label, NewIntersectedList, SaveTree),
 
116
      firstPassHelper(Labels, Liveness, NewCFG, UpdatedSaveTree);
118
117
     true ->
119
 
      firstPassHelper(Labels, Liveness, NewCFG,SaveTree)
 
118
      firstPassHelper(Labels, Liveness, NewCFG, SaveTree)
120
119
  end;
121
120
firstPassHelper([], _, CFG, SaveTree) ->
122
121
  {CFG, SaveTree}.
125
124
firstPassDoBlock(Insts, LiveOut, IntersectedSaveList) -> 
126
125
  lists:foldr(fun firstPassDoInsn/2, {LiveOut,IntersectedSaveList,[]}, Insts).
127
126
 
128
 
firstPassDoInsn(I, {LiveOut,IntersectedSaveList,PrevInsts} ) ->
 
127
firstPassDoInsn(I, {LiveOut,IntersectedSaveList,PrevInsts}) ->
129
128
  case I of
130
129
    #pseudo_call{} ->
131
130
      do_pseudo_call(I, {LiveOut,IntersectedSaveList,PrevInsts});
132
131
    _ -> % other instructions
133
132
      DefinedList = from_list( ?HIPE_X86_LIVENESS:defines(I)),
134
133
      UsedList = from_list(?HIPE_X86_LIVENESS:uses(I)),
135
 
      
136
134
      NewLiveOut = subtract(union(LiveOut, UsedList), DefinedList),
137
 
      NewIntersectedSaveList = subtract(IntersectedSaveList, DefinedList), 
138
 
      
 
135
      NewIntersectedSaveList = subtract(IntersectedSaveList, DefinedList),
139
136
      {NewLiveOut, NewIntersectedSaveList, [I|PrevInsts]}
140
137
  end.
141
138
 
162
159
      []
163
160
  end.
164
161
 
165
 
%% Performs the second pass of the algoritm.
 
162
%% Performs the second pass of the algorithm.
166
163
%% It basically eliminates the unnecessary spills and introduces restores.
167
164
%% Works top down
168
165
secondPass(CFG0) ->
306
303
  NewCFG = hipe_x86_cfg:bb_add(CFG, NextLabel, NewBlock),
307
304
  {NewCFG, NewPseudoCall}.
308
305
 
309
 
%% used instead of hipe_x86_cfg:redirect_jmp since it does not handle pseudo_call calls.
 
306
%% used instead of hipe_x86_cfg:redirect_jmp since it does not handle
 
307
%% pseudo_call calls.
310
308
redirect_pseudo_call(I = #pseudo_call{contlab=ContLabel}, Old, New) ->
311
309
  case Old =:= ContLabel of
312
310
    true  -> I#pseudo_call{contlab=New};
323
321
%% Set operations where the module name is an easily changeable macro
324
322
%%---------------------------------------------------------------------
325
323
 
326
 
union(Set1,Set2) ->
327
 
  ?SET_MODULE:union(Set1,Set2).
 
324
union(Set1, Set2) ->
 
325
  ?SET_MODULE:union(Set1, Set2).
328
326
 
329
327
setSize(Set) ->
330
328
  ?SET_MODULE:size(Set).