~rdoering/ubuntu/lucid/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/compiler/src/cerl_inline.erl

  • Committer: Elliot Murphy
  • Date: 2009-12-22 02:56:21 UTC
  • mfrom: (3.3.5 sid)
  • Revision ID: elliot@elliotmurphy.com-20091222025621-qv3rja8gbpiabkbe
* Merge with Debian testing; remaining Ubuntu changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to. (LP #438365)
  - 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.
* Fixed dialyzer(1) manpage which was placed into section 3 and conflicted
  with dialyzer(3erl).
* New upstream release (it adds a new binary package erlang-erl-docgen).
* Refreshed patches, removed most of emacs.patch which is applied upstream.
* Linked run_test binary from erlang-common-test package to /usr/bin.
* Fixed VCS headers in debian/control.
* Moved from prebuilt manpages to generated from sources. This adds
  erlang-manpages binary package and xsltproc build dependency.

Show diffs side-by-side

added added

removed removed

Lines of Context:
128
128
weight(call) -> 3;      % Assume remote-calls as efficient as `apply'.
129
129
weight(primop) -> 2;    % Assume more efficient than `apply'.
130
130
weight(binary) -> 4;    % Initialisation base cost.
131
 
weight(bitstr) -> 3;   % Coding/decoding a value; like a primop.
 
131
weight(bitstr) -> 3;    % Coding/decoding a value; like a primop.
132
132
weight(module) -> 1.    % Like a letrec with a constant body
133
133
 
134
134
%% These "reference" structures are used for variables and function
164
164
%% Use compile option `{core_transform, inline}' to insert this as a
165
165
%% compilation pass.
166
166
 
 
167
-spec core_transform(cerl:cerl(), [compile:option()]) -> cerl:cerl().
 
168
 
167
169
core_transform(Code, Opts) ->
168
170
    cerl:to_records(transform(cerl:from_records(Code), Opts)).
169
171
 
 
172
-spec transform(cerl:cerl()) -> cerl:cerl().
 
173
 
170
174
transform(Tree) ->
171
175
    transform(Tree, []).
172
176
 
 
177
-spec transform(cerl:cerl(), [compile:option()]) -> cerl:cerl().
 
178
 
173
179
transform(Tree, Opts) ->
174
180
    main(Tree, value, Opts).
175
181
 
1189
1195
 
1190
1196
i_catch(E, Ctxt, Ren, Env, S) ->
1191
1197
    %% We cannot propagate application contexts into the catch.
1192
 
    {E1, S1} = i(catch_body(E), safe_context(Ctxt), Ren, Env, S),
 
1198
    {E1, S1} = ES1 = i(catch_body(E), safe_context(Ctxt), Ren, Env, S),
1193
1199
    case is_safe(E1) of
1194
1200
        true ->
1195
1201
            %% The `catch' wrapper can be dropped in this case.
1196
 
            {E1, S1};
 
1202
            ES1;
1197
1203
        false ->
1198
1204
            S2 = count_size(weight('catch'), S1),
1199
1205
            {update_c_catch(E, E1), S2}
1811
1817
                values ->
1812
1818
                    is_safe_list(values_es(E));
1813
1819
                'seq' ->
1814
 
                    case is_safe(seq_arg(E)) of
1815
 
                        true ->
1816
 
                            is_safe(seq_body(E));
1817
 
                        false ->
1818
 
                            false
1819
 
                    end;
 
1820
                    is_safe(seq_arg(E)) andalso is_safe(seq_body(E));
1820
1821
                'let' ->
1821
 
                    case is_safe(let_arg(E)) of
1822
 
                        true ->
1823
 
                            is_safe(let_body(E));
1824
 
                        false ->
1825
 
                            false
1826
 
                    end;
 
1822
                    is_safe(let_arg(E)) andalso is_safe(let_body(E));
1827
1823
                letrec ->
1828
1824
                    is_safe(letrec_body(E));
1829
1825
                'try' ->
1831
1827
                    %% be modifying the state; thus, even if the body is
1832
1828
                    %% safe, the try-expression as a whole would not be.
1833
1829
                    %% If the argument is safe, the handler is not used.
1834
 
                    case is_safe(try_arg(E)) of
1835
 
                        true ->
1836
 
                            is_safe(try_body(E));
1837
 
                        false ->
1838
 
                            false
1839
 
                    end;
 
1830
                    is_safe(try_arg(E)) andalso is_safe(try_body(E));
1840
1831
                'catch' ->
1841
1832
                    is_safe(catch_body(E));
1842
1833
                call ->
1843
1834
                    M = call_module(E),
1844
1835
                    F = call_name(E),
1845
 
                    case is_c_atom(M) and is_c_atom(F) of
 
1836
                    case is_c_atom(M) andalso is_c_atom(F) of
1846
1837
                        true ->
1847
1838
                            As = call_args(E),
1848
 
                            case is_safe_list(As) of
1849
 
                                true ->
1850
 
                                    is_safe_call(atom_val(M),
1851
 
                                                 atom_val(F),
1852
 
                                                 length(As));
1853
 
                                false ->
1854
 
                                    false
1855
 
                            end;
 
1839
                            is_safe_list(As) andalso
 
1840
                                is_safe_call(atom_val(M),
 
1841
                                             atom_val(F),
 
1842
                                             length(As));
1856
1843
                        false ->
1857
1844
                            false
1858
1845
                    end;
1913
1900
%% particular variable in the source code can be reused.
1914
1901
 
1915
1902
bind_locals(Vs, Ren, Env, S) ->
1916
 
    Opnds = lists:duplicate(length(Vs), undefined),
 
1903
    Opnds = [undefined || _ <- Vs],
1917
1904
    bind_locals(Vs, Opnds, Ren, Env, S).
1918
1905
 
1919
1906
bind_locals(Vs, Opnds, Ren, Env, S) ->
2162
2149
                    T1 = {data_type(E1), data_arity(E1)},
2163
2150
                    T2 = {data_type(E2), data_arity(E2)},
2164
2151
                    %% Note that we must test for exact equality.
2165
 
                    if T1 =:= T2 ->
2166
 
                            equivalent_lists(data_es(E1), data_es(E2),
2167
 
                                             Env);
2168
 
                       true ->
2169
 
                            false
2170
 
                    end;
 
2152
                    T1 =:= T2 andalso
 
2153
                        equivalent_lists(data_es(E1), data_es(E2), Env);
2171
2154
                false ->
2172
2155
                    false
2173
2156
            end;
2178
2161
                        true ->
2179
2162
                            N1 = var_name(E1),
2180
2163
                            N2 = var_name(E2),
2181
 
                            if N1 =:= N2 ->
2182
 
                                    not ordsets:is_element(N1, Env);
2183
 
                               true ->
2184
 
                                    false
2185
 
                            end;
 
2164
                            N1 =:= N2 andalso not ordsets:is_element(N1, Env);
2186
2165
                        false ->
2187
2166
                            false
2188
2167
                    end;
2422
2401
            false
2423
2402
    end.
2424
2403
 
2425
 
all_static([E | Es]) ->
2426
 
    case is_literal(result(E)) of
2427
 
        true ->
2428
 
            all_static(Es);
2429
 
        false ->
2430
 
            false
2431
 
    end;
2432
 
all_static([]) ->
2433
 
    true.
 
2404
all_static(Es) ->
 
2405
    lists:all(fun (E) -> is_literal(result(E)) end, Es).
2434
2406
 
2435
2407
set_clause_bodies([C | Cs], B) ->
2436
2408
    [update_c_clause(C, clause_pats(C), clause_guard(C), B)
2539
2511
-record(app_flags, {lab, inlined = false}).
2540
2512
 
2541
2513
st__new(Effort, Size, Unroll) ->
 
2514
    EtsOpts = [set, private, {keypos, 2}],
2542
2515
    #state{free = 0,
2543
2516
           size = counter__new_passive(Size),
2544
2517
           effort = counter__new_passive(Effort),
2545
2518
           unroll = Unroll,
2546
2519
           cache = dict:new(),
2547
 
           var_flags = ets:new(var, [set, private, {keypos, 2}]),
2548
 
           opnd_flags = ets:new(opnd, [set, private, {keypos, 2}]),
2549
 
           app_flags = ets:new(app, [set, private, {keypos, 2}])}.
 
2520
           var_flags = ets:new(var, EtsOpts),
 
2521
           opnd_flags = ets:new(opnd, EtsOpts),
 
2522
           app_flags = ets:new(app, EtsOpts)}.
2550
2523
 
2551
2524
st__new_loc(S) ->
2552
2525
    N = S#state.free,