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

« back to all changes in this revision

Viewing changes to lib/stdlib/src/erl_expand_records.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
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2005-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2005-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
%% Purpose : Expand records into tuples.
95
95
forms([], St) -> {[],St}.
96
96
 
97
97
clauses([{clause,Line,H0,G0,B0} | Cs0], St0) ->
98
 
    {H,St1} = head(H0, St0),
99
 
    {G,St2} = guard(G0, St1),
 
98
    {H1,St1} = head(H0, St0),
 
99
    {G1,St2} = guard(G0, St1),
 
100
    {H,G} = optimize_is_record(H1, G1, St2),
100
101
    {B,St3} = exprs(B0, St2),
101
102
    {Cs,St4} = clauses(Cs0, St3),
102
103
    {[{clause,Line,H,G,B} | Cs],St4};
191
192
 
192
193
normalise_test(atom, 1)      -> is_atom;
193
194
normalise_test(binary, 1)    -> is_binary;
194
 
normalise_test(constant, 1)  -> is_constant;
195
195
normalise_test(float, 1)     -> is_float;
196
196
normalise_test(function, 1)  -> is_function;
197
197
normalise_test(integer, 1)   -> is_integer;
346
346
    {{'fun',Line,{clauses,Cs}},St1};
347
347
expr({call,Line,{atom,_,is_record},[A,{atom,_,Name}]}, St) ->
348
348
    record_test(Line, A, Name, St);
349
 
expr({'cond',Line,Cs0}, St0) ->
350
 
    {Cs,St1} = clauses(Cs0, St0),
351
 
    {{'cond',Line,Cs},St1};
352
349
expr({call,Line,{remote,_,{atom,_,erlang},{atom,_,is_record}},
353
350
      [A,{atom,_,Name}]}, St) ->
354
351
    record_test(Line, A, Name, St);
804
801
        error -> no
805
802
    end.
806
803
 
 
804
%%%
 
805
%%% Replace is_record/3 in guards with matching if possible.
 
806
%%%
 
807
 
 
808
optimize_is_record(H0, G0, #exprec{compile=Opts}) ->
 
809
    case opt_rec_vars(G0) of
 
810
        [] ->
 
811
            {H0,G0};
 
812
        Rs0 ->
 
813
            case lists:member(no_is_record_optimization, Opts) of
 
814
                true ->
 
815
                    {H0,G0};
 
816
                false ->
 
817
                    {H,Rs} = opt_pattern_list(H0, Rs0),
 
818
                    G = opt_remove(G0, Rs),
 
819
                    {H,G}
 
820
            end
 
821
    end.
 
822
 
 
823
 
 
824
%% opt_rec_vars(Guards) -> Vars.
 
825
%%  Search through the guard expression, looking for
 
826
%%  variables referenced in those is_record/3 calls that
 
827
%%  will fail the entire guard if they evaluate to 'false'
 
828
%%
 
829
%%  In the following code
 
830
%%
 
831
%%      f(X, Y, Z) when is_record(X, r1) andalso
 
832
%%                           (is_record(Y, r2) orelse is_record(Z, r3))
 
833
%%
 
834
%%  the entire guard will be false if the record test for
 
835
%%  X fails, and the clause can be rewritten to:
 
836
%%
 
837
%%      f({r1,...}=X, Y, Z) when true andalso
 
838
%%                              (is_record(Y, r2) or is_record(Z, r3))
 
839
%%
 
840
opt_rec_vars([G|Gs]) ->
 
841
    Rs = opt_rec_vars_1(G, orddict:new()),
 
842
    opt_rec_vars(Gs, Rs);
 
843
opt_rec_vars([]) -> orddict:new().
 
844
 
 
845
opt_rec_vars([G|Gs], Rs0) ->
 
846
    Rs1 = opt_rec_vars_1(G, orddict:new()),
 
847
    Rs = ordsets:intersection(Rs0, Rs1),
 
848
    opt_rec_vars(Gs, Rs);
 
849
opt_rec_vars([], Rs) -> Rs.
 
850
 
 
851
opt_rec_vars_1([T|Ts], Rs0) ->
 
852
    Rs = opt_rec_vars_2(T, Rs0),
 
853
    opt_rec_vars_1(Ts, Rs);
 
854
opt_rec_vars_1([], Rs) -> Rs.
 
855
 
 
856
opt_rec_vars_2({op,_,'and',A1,A2}, Rs) ->
 
857
    opt_rec_vars_1([A1,A2], Rs);
 
858
opt_rec_vars_2({op,_,'andalso',A1,A2}, Rs) ->
 
859
    opt_rec_vars_1([A1,A2], Rs);
 
860
opt_rec_vars_2({op,_,'orelse',Arg,{atom,_,fail}}, Rs) ->
 
861
    %% Since the second argument guarantees failure,
 
862
    %% it is safe to inspect the first argument.
 
863
    opt_rec_vars_2(Arg, Rs);
 
864
opt_rec_vars_2({call,_,{remote,_,{atom,_,erlang},{atom,_,is_record}},
 
865
                [{var,_,V},{atom,_,Tag},{integer,_,Sz}]}, Rs) ->
 
866
    orddict:store(V, {Tag,Sz}, Rs);
 
867
opt_rec_vars_2({call,_,{atom,_,is_record},
 
868
                [{var,_,V},{atom,_,Tag},{integer,_,Sz}]}, Rs) ->
 
869
    orddict:store(V, {Tag,Sz}, Rs);
 
870
opt_rec_vars_2(_, Rs) -> Rs.
 
871
 
 
872
opt_pattern_list(Ps, Rs) ->
 
873
    opt_pattern_list(Ps, Rs, []).
 
874
 
 
875
opt_pattern_list([P0|Ps], Rs0, Acc) ->
 
876
    {P,Rs} = opt_pattern(P0, Rs0),
 
877
    opt_pattern_list(Ps, Rs, [P|Acc]);
 
878
opt_pattern_list([], Rs, Acc) ->
 
879
    {reverse(Acc),Rs}.
 
880
 
 
881
opt_pattern({var,_,V}=Var, Rs0) ->
 
882
    case orddict:find(V, Rs0) of
 
883
        {ok,{Tag,Sz}} ->
 
884
            Rs = orddict:store(V, {remove,Tag,Sz}, Rs0),
 
885
            {opt_var(Var, Tag, Sz),Rs};
 
886
        _ ->
 
887
            {Var,Rs0}
 
888
    end;
 
889
opt_pattern({cons,Line,H0,T0}, Rs0) ->
 
890
    {H,Rs1} = opt_pattern(H0, Rs0),
 
891
    {T,Rs} = opt_pattern(T0, Rs1),
 
892
    {{cons,Line,H,T},Rs};
 
893
opt_pattern({tuple,Line,Es0}, Rs0) ->
 
894
    {Es,Rs} = opt_pattern_list(Es0, Rs0),
 
895
    {{tuple,Line,Es},Rs};
 
896
opt_pattern({match,Line,Pa0,Pb0}, Rs0) ->
 
897
    {Pa,Rs1} = opt_pattern(Pa0, Rs0),
 
898
    {Pb,Rs} = opt_pattern(Pb0, Rs1),
 
899
    {{match,Line,Pa,Pb},Rs};
 
900
opt_pattern(P, Rs) -> {P,Rs}.
 
901
 
 
902
opt_var({var,Line,_}=Var, Tag, Sz) ->
 
903
    Rp = record_pattern(2, -1, ignore, Sz, Line, [{atom,Line,Tag}]),
 
904
    {match,Line,{tuple,Line,Rp},Var}.
 
905
 
 
906
opt_remove(Gs, Rs) ->
 
907
    [opt_remove_1(G, Rs) || G <- Gs].
 
908
 
 
909
opt_remove_1(Ts, Rs) ->
 
910
    [opt_remove_2(T, Rs) || T <- Ts].
 
911
 
 
912
opt_remove_2({op,L,'and'=Op,A1,A2}, Rs) ->
 
913
    {op,L,Op,opt_remove_2(A1, Rs),opt_remove_2(A2, Rs)};
 
914
opt_remove_2({op,L,'andalso'=Op,A1,A2}, Rs) ->
 
915
    {op,L,Op,opt_remove_2(A1, Rs),opt_remove_2(A2, Rs)};
 
916
opt_remove_2({op,L,'orelse',A1,A2}, Rs) ->
 
917
    {op,L,'orelse',opt_remove_2(A1, Rs),A2};
 
918
opt_remove_2({call,Line,{remote,_,{atom,_,erlang},{atom,_,is_record}},
 
919
              [{var,_,V},{atom,_,Tag},{integer,_,Sz}]}=A, Rs) ->
 
920
    case orddict:find(V, Rs) of
 
921
        {ok,{remove,Tag,Sz}} ->
 
922
            {atom,Line,true};
 
923
        _ ->
 
924
            A
 
925
    end;
 
926
opt_remove_2({call,Line,{atom,_,is_record},
 
927
              [{var,_,V},{atom,_,Tag},{integer,_,Sz}]}=A, Rs) ->
 
928
    case orddict:find(V, Rs) of
 
929
        {ok,{remove,Tag,Sz}} ->
 
930
            {atom,Line,true};
 
931
        _ ->
 
932
            A
 
933
    end;
 
934
opt_remove_2(A, _) -> A.
 
935
 
807
936
neg_line(L) ->
808
937
    erl_parse:set_line(L, fun(Line) -> -abs(Line) end).