~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/options1_SUITE_data/src/compiler/beam_dict.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%%
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%%
 
12
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
 
13
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
 
14
%% AB. All Rights Reserved.''
 
15
%%
 
16
%%     $Id: beam_dict.erl,v 1.1 2008/12/17 09:53:41 mikpe Exp $
 
17
%%
 
18
%% Purpose : Maintain atom, import, and export tables for assembler.
 
19
 
 
20
-module(beam_dict).
 
21
 
 
22
-export([new/0, opcode/2, highest_opcode/1,
 
23
         atom/2, local/4, export/4, import/4, string/2, lambda/5,
 
24
         atom_table/1, local_table/1, export_table/1, import_table/1,
 
25
         string_table/1,lambda_table/1]).
 
26
 
 
27
-record(asm_dict,
 
28
        {atoms = [],                            % [{Index, Atom}]
 
29
         exports = [],                          % [{F, A, Label}]
 
30
         locals = [],                           % [{F, A, Label}]
 
31
         imports = [],                          % [{Index, {M, F, A}]
 
32
         strings = [],                          % Deep list of characters
 
33
         lambdas = [],                          % [{...}]
 
34
         next_atom = 1,
 
35
         next_import = 0,
 
36
         string_offset = 0,
 
37
         highest_opcode = 0
 
38
        }).
 
39
 
 
40
new() ->
 
41
    #asm_dict{}.
 
42
 
 
43
%% Remembers highest opcode.
 
44
 
 
45
opcode(Op, Dict) when Dict#asm_dict.highest_opcode > Op -> Dict;
 
46
opcode(Op, Dict) -> Dict#asm_dict{highest_opcode=Op}.
 
47
 
 
48
%% Returns the highest opcode encountered.
 
49
 
 
50
highest_opcode(#asm_dict{highest_opcode=Op}) -> Op.
 
51
 
 
52
%% Returns the index for an atom (adding it to the atom table if necessary).
 
53
%%    atom(Atom, Dict) -> {Index, Dict'}
 
54
 
 
55
atom(Atom, Dict) when atom(Atom) ->
 
56
    NextIndex = Dict#asm_dict.next_atom,
 
57
    case lookup_store(Atom, Dict#asm_dict.atoms, NextIndex) of
 
58
        {Index, _, NextIndex} ->
 
59
            {Index, Dict};
 
60
        {Index, Atoms, NewIndex} ->
 
61
            {Index, Dict#asm_dict{atoms=Atoms, next_atom=NewIndex}}
 
62
    end.
 
63
 
 
64
%% Remembers an exported function.
 
65
%%    export(Func, Arity, Label, Dict) -> Dict'
 
66
 
 
67
export(Func, Arity, Label, Dict0) when atom(Func), integer(Arity), integer(Label) ->
 
68
    {Index, Dict1} = atom(Func, Dict0),
 
69
    Dict1#asm_dict{exports = [{Index, Arity, Label}| Dict1#asm_dict.exports]}.
 
70
 
 
71
%% Remembers a local function.
 
72
%%    local(Func, Arity, Label, Dict) -> Dict'
 
73
 
 
74
local(Func, Arity, Label, Dict0) when atom(Func), integer(Arity), integer(Label) ->
 
75
    {Index,Dict1} = atom(Func, Dict0),
 
76
    Dict1#asm_dict{locals = [{Index,Arity,Label}| Dict1#asm_dict.locals]}.
 
77
 
 
78
%% Returns the index for an import entry (adding it to the import table if necessary).
 
79
%%    import(Mod, Func, Arity, Dict) -> {Index, Dict'}
 
80
 
 
81
import(Mod, Func, Arity, Dict) when atom(Mod), atom(Func), integer(Arity) ->
 
82
    NextIndex = Dict#asm_dict.next_import,
 
83
    case lookup_store({Mod, Func, Arity}, Dict#asm_dict.imports, NextIndex) of
 
84
        {Index, _, NextIndex} ->
 
85
            {Index, Dict};
 
86
        {Index, Imports, NewIndex} ->
 
87
            {_, D1} = atom(Mod, Dict#asm_dict{imports=Imports, next_import=NewIndex}),
 
88
            {_, D2} = atom(Func, D1),
 
89
            {Index, D2}
 
90
    end.
 
91
 
 
92
%% Returns the index for a string in the string table (adding the string to the
 
93
%% table if necessary).
 
94
%%    string(String, Dict) -> {Offset, Dict'}
 
95
 
 
96
string(Str, Dict) when list(Str) ->
 
97
    #asm_dict{strings = Strings, string_offset = NextOffset} = Dict,
 
98
    case old_string(Str, Strings) of
 
99
        {true, Offset} ->
 
100
            {Offset, Dict};
 
101
        false ->
 
102
            NewDict = Dict#asm_dict{strings = Strings++Str,
 
103
                                    string_offset = NextOffset+length(Str)},
 
104
            {NextOffset, NewDict}
 
105
    end.
 
106
 
 
107
%% Returns the index for a funentry (adding it to the table if necessary).
 
108
%%    lambda(Dict, Lbl, Index, Uniq, NumFree) -> {Index,Dict'}
 
109
 
 
110
lambda(Lbl, Index, OldUniq, NumFree, #asm_dict{lambdas=Lambdas0}=Dict) ->
 
111
    OldIndex = length(Lambdas0),
 
112
    Lambdas = [{Lbl,{OldIndex,Lbl,Index,NumFree,OldUniq}}|Lambdas0],
 
113
    {OldIndex,Dict#asm_dict{lambdas=Lambdas}}.
 
114
 
 
115
%% Returns the atom table.
 
116
%%    atom_table(Dict) -> [Length,AtomString...]
 
117
 
 
118
atom_table(#asm_dict{atoms=Atoms, next_atom=NumAtoms}) ->
 
119
    Sorted = lists:sort(Atoms),
 
120
    Fun = fun({_, A}) ->
 
121
                  L = atom_to_list(A),
 
122
                  [length(L)|L]
 
123
          end,
 
124
    {NumAtoms-1, lists:map(Fun, Sorted)}.
 
125
 
 
126
%% Returns the table of local functions.
 
127
%%    local_table(Dict) -> {NumLocals, [{Function, Arity, Label}...]}
 
128
 
 
129
local_table(#asm_dict{locals = Locals}) ->
 
130
    {length(Locals),Locals}.
 
131
 
 
132
%% Returns the export table.
 
133
%%    export_table(Dict) -> {NumExports, [{Function, Arity, Label}...]}
 
134
 
 
135
export_table(#asm_dict{exports = Exports}) ->
 
136
    {length(Exports), Exports}.
 
137
 
 
138
%% Returns the import table.
 
139
%%    import_table(Dict) -> {NumImports, [{Module, Function, Arity}...]}
 
140
 
 
141
import_table(Dict) ->
 
142
    #asm_dict{imports = Imports, next_import = NumImports} = Dict,
 
143
    Sorted = lists:sort(Imports),
 
144
    Fun = fun({_, {Mod, Func, Arity}}) ->
 
145
                  {Atom0, _} = atom(Mod, Dict),
 
146
                  {Atom1, _} = atom(Func, Dict),
 
147
                  {Atom0, Atom1, Arity}
 
148
          end,
 
149
    {NumImports, lists:map(Fun, Sorted)}.
 
150
 
 
151
string_table(#asm_dict{strings = Strings, string_offset = Size}) ->
 
152
    {Size, Strings}.
 
153
 
 
154
lambda_table(#asm_dict{locals=Loc0,lambdas=Lambdas0}) ->
 
155
    Lambdas1 = sofs:relation(Lambdas0),
 
156
    Loc = sofs:relation([{Lbl,{F,A}} || {F,A,Lbl} <- Loc0]),
 
157
    Lambdas2 = sofs:relative_product1(Lambdas1, Loc),
 
158
    Lambdas = [<<F:32,A:32,Lbl:32,Index:32,NumFree:32,OldUniq:32>> ||
 
159
                  {{_,Lbl,Index,NumFree,OldUniq},{F,A}} <- sofs:to_external(Lambdas2)],
 
160
    {length(Lambdas),Lambdas}.
 
161
 
 
162
%%% Local helper functions.
 
163
 
 
164
lookup_store(Key, Dict, NextIndex) ->
 
165
    case catch lookup_store1(Key, Dict, NextIndex) of
 
166
        Index when integer(Index) ->
 
167
            {Index, Dict, NextIndex};
 
168
        {Index, NewDict} ->
 
169
            {Index, NewDict, NextIndex+1}
 
170
    end.
 
171
 
 
172
lookup_store1(Key, [Pair|Dict], NextIndex) when Key > element(2, Pair) ->
 
173
    {Index, NewDict} = lookup_store1(Key, Dict, NextIndex),
 
174
    {Index, [Pair|NewDict]};
 
175
lookup_store1(Key, [{Index, Key}|_Dict], _NextIndex) ->
 
176
    throw(Index);
 
177
lookup_store1(Key, Dict, NextIndex) ->
 
178
    {NextIndex, [{NextIndex, Key}|Dict]}.
 
179
 
 
180
%% Search for string Str in the string pool Pool.
 
181
%%   old_string(Str, Pool) -> false | {true, Offset}
 
182
 
 
183
old_string(Str, Pool) ->
 
184
    old_string(Str, Pool, 0).
 
185
 
 
186
old_string([C|Str], [C|Pool], Index) ->
 
187
    case lists:prefix(Str, Pool) of
 
188
        true ->
 
189
            {true, Index};
 
190
        false ->
 
191
            old_string([C|Str], Pool, Index+1)
 
192
    end;
 
193
old_string(Str, [_|Pool], Index) ->
 
194
    old_string(Str, Pool, Index+1);
 
195
old_string(_Str, [], _Index) ->
 
196
    false.