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

« back to all changes in this revision

Viewing changes to lib/stdlib/src/ets.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 1996-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1996-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
-module(ets).
42
42
 
43
43
-export([i/0, i/1, i/2, i/3]).
44
44
 
45
 
%%------------------------------------------------------------------------------
 
45
-export_type([tab/0, tid/0]).
 
46
 
 
47
%%-----------------------------------------------------------------------------
46
48
 
47
49
-type tab()        :: atom() | tid().
48
50
 
 
51
%% a similar definition is also in erl_types
 
52
-opaque tid()      :: integer().
 
53
 
49
54
-type ext_info()   :: 'md5sum' | 'object_count'.
50
55
-type protection() :: 'private' | 'protected' | 'public'.
51
56
-type type()       :: 'bag' | 'duplicate_bag' | 'ordered_set' | 'set'.
63
68
-type match_pattern() :: atom() | tuple().
64
69
-type match_specs()   :: [{match_pattern(), [_], [_]}].
65
70
 
66
 
%%------------------------------------------------------------------------------
 
71
%%-----------------------------------------------------------------------------
67
72
 
68
73
%% The following functions used to be found in this module, but
69
74
%% are now BIFs (i.e. implemented in C).
230
235
            erlang:error(Unexpected,[EtsTable,DetsTable])
231
236
    end.
232
237
 
233
 
-spec to_dets(tab(), dets:tab_name()) -> tab().
 
238
-spec to_dets(tab(), dets:tab_name()) -> dets:tab_name().
234
239
 
235
240
to_dets(EtsTable, DetsTable) ->
236
241
    case (catch dets:from_ets(DetsTable, EtsTable)) of
507
512
 
508
513
file2tab(File, Opts) ->
509
514
    try
510
 
        {ok,Verify} = parse_f2t_opts(Opts,false),
 
515
        {ok,Verify,TabArg} = parse_f2t_opts(Opts,false,[]),
511
516
        Name = make_ref(),
512
517
        {ok, Major, Minor, FtOptions, MD5State, FullHeader, DLContext} = 
513
518
            case disk_log:open([{name, Name}, 
535
540
                true ->
536
541
                    ok
537
542
            end,
538
 
            {ok, Tab, HeadCount} = create_tab(FullHeader),
 
543
            {ok, Tab, HeadCount} = create_tab(FullHeader, TabArg),
539
544
            StrippedOptions =                              
540
545
                case Verify of
541
546
                    true ->
622
627
            end,
623
628
            {ok,Tab};
624
629
        {ok,{FinalMD5State,FinalCount,['$end_of_table',LastInfo],_}} ->
625
 
            ECount = case lists:keysearch(count,1,LastInfo) of
626
 
                         {value,{count,N}} ->
 
630
            ECount = case lists:keyfind(count,1,LastInfo) of
 
631
                         {count,N} ->
627
632
                             N;
628
633
                         _ ->
629
634
                             false
630
635
                     end,
631
 
            EMD5 = case lists:keysearch(md5,1,LastInfo) of
632
 
                         {value,{md5,M}} ->
 
636
            EMD5 = case lists:keyfind(md5,1,LastInfo) of
 
637
                         {md5,M} ->
633
638
                             M;
634
639
                         _ ->
635
640
                             false
671
676
            {ok,Tab}
672
677
    end.
673
678
 
674
 
parse_f2t_opts([],Verify) ->
675
 
    {ok,Verify};
676
 
parse_f2t_opts([{verify, true}|T],_OV) ->
677
 
    parse_f2t_opts(T,true);
678
 
parse_f2t_opts([{verify,false}|T],OV) ->
679
 
    parse_f2t_opts(T,OV);
680
 
parse_f2t_opts([Unexpected|_],_) ->
 
679
parse_f2t_opts([],Verify,Tab) ->
 
680
    {ok,Verify,Tab};
 
681
parse_f2t_opts([{verify, true}|T],_OV,Tab) ->
 
682
    parse_f2t_opts(T,true,Tab);
 
683
parse_f2t_opts([{verify,false}|T],OV,Tab) ->
 
684
    parse_f2t_opts(T,OV,Tab);
 
685
parse_f2t_opts([{table,Tab}|T],OV,[]) ->
 
686
    parse_f2t_opts(T,OV,Tab);
 
687
parse_f2t_opts([Unexpected|_],_,_) ->
681
688
    throw({unknown_option,Unexpected});
682
 
parse_f2t_opts(Malformed,_) ->
 
689
parse_f2t_opts(Malformed,_,_) ->
683
690
    throw({malformed_option,Malformed}).
684
691
                           
685
692
count_mandatory([]) ->
742
749
                        false ->
743
750
                            throw(badfile);
744
751
                        true ->
745
 
                            Major = case lists:keysearch(major,1,L) of
746
 
                                        {value,{major,Maj}} ->
 
752
                            Major = case lists:keyfind(major,1,L) of
 
753
                                        {major,Maj} ->
747
754
                                            Maj;
748
755
                                        _ ->
749
756
                                            0
750
757
                                    end,
751
 
                            Minor = case lists:keysearch(minor,1,L) of
752
 
                                        {value,{minor,Min}} ->
 
758
                            Minor = case lists:keyfind(minor,1,L) of
 
759
                                        {minor,Min} ->
753
760
                                            Min;
754
761
                                        _ ->
755
762
                                            0
756
763
                                    end,
757
764
                            FtOptions = 
758
 
                                case lists:keysearch(extended_info,1,L) of
759
 
                                    {value,{extended_info,I}} 
760
 
                                    when is_list(I) ->
 
765
                                case lists:keyfind(extended_info,1,L) of
 
766
                                    {extended_info,I} when is_list(I) ->
761
767
                                        #filetab_options
762
768
                                            {
763
769
                                            object_count = 
786
792
    end;
787
793
 
788
794
get_header_data(Name, false) ->
789
 
   case wrap_chunk(Name,start,1,false) of 
 
795
   case wrap_chunk(Name, start, 1, false) of
790
796
       {C,[Tup]} when is_tuple(Tup) ->
791
797
           L = tuple_to_list(Tup),
792
798
           case verify_header_mandatory(L) of
793
799
               false ->
794
800
                   throw(badfile);
795
801
               true ->
796
 
                   Major = case lists:keysearch(major_version,1,L) of
797
 
                               {value,{major_version,Maj}} ->
 
802
                   Major = case lists:keyfind(major_version, 1, L) of
 
803
                               {major_version, Maj} ->
798
804
                                   Maj;
799
805
                               _ ->
800
806
                                   0
801
807
                           end,
802
 
                   Minor = case lists:keysearch(minor_version,1,L) of
803
 
                               {value,{minor_version,Min}} ->
 
808
                   Minor = case lists:keyfind(minor_version, 1, L) of
 
809
                               {minor_version, Min} ->
804
810
                                   Min;
805
811
                               _ ->
806
812
                                   0
807
813
                           end,
808
814
                   FtOptions = 
809
 
                       case lists:keysearch(extended_info,1,L) of
810
 
                           {value,{extended_info,I}} 
811
 
                           when is_list(I) ->
 
815
                       case lists:keyfind(extended_info, 1, L) of
 
816
                           {extended_info, I} when is_list(I) ->
812
817
                               #filetab_options
813
818
                                         {
814
819
                                         object_count = 
825
830
           throw(badfile)
826
831
    end.
827
832
 
828
 
md5_and_convert([],MD5State,Count) ->
 
833
md5_and_convert([], MD5State, Count) ->
829
834
    {[],MD5State,Count,[]};
830
 
md5_and_convert([H|T],MD5State,Count) when is_binary(H) ->
 
835
md5_and_convert([H|T], MD5State, Count) when is_binary(H) ->
831
836
    case (catch binary_to_term(H)) of
832
837
        {'EXIT', _} ->
833
838
            md5_and_convert(T,MD5State,Count);
834
 
        ['$end_of_table',Dat] ->
835
 
           {[],MD5State,Count,['$end_of_table',Dat]}; 
 
839
        ['$end_of_table',_Dat] = L ->
 
840
           {[],MD5State,Count,L};
836
841
        Term ->
837
 
            X = erlang:md5_update(MD5State,H),
838
 
            {Rest,NewMD5,NewCount,NewLast} = md5_and_convert(T,X,Count+1),
 
842
            X = erlang:md5_update(MD5State, H),
 
843
            {Rest,NewMD5,NewCount,NewLast} = md5_and_convert(T, X, Count+1),
839
844
            {[Term | Rest],NewMD5,NewCount,NewLast}
840
845
    end.
841
 
scan_for_endinfo([],Count) ->
 
846
 
 
847
scan_for_endinfo([], Count) ->
842
848
    {[],Count,[]};
843
 
scan_for_endinfo([['$end_of_table',Dat]],Count) ->
 
849
scan_for_endinfo([['$end_of_table',Dat]], Count) ->
844
850
    {['$end_of_table',Dat],Count,[]};
845
 
scan_for_endinfo([Term|T],Count) ->
846
 
    {NewLast,NCount,Rest} = scan_for_endinfo(T,Count+1),
 
851
scan_for_endinfo([Term|T], Count) ->
 
852
    {NewLast,NCount,Rest} = scan_for_endinfo(T, Count+1),
847
853
    {NewLast,NCount,[Term | Rest]}.
848
854
 
849
855
load_table(ReadFun, State, Tab) ->
852
858
        [] ->
853
859
            {ok,NewState};
854
860
        List ->
855
 
            ets:insert(Tab,List),
856
 
            load_table(ReadFun,NewState,Tab)
 
861
            ets:insert(Tab, List),
 
862
            load_table(ReadFun, NewState, Tab)
857
863
    end.
858
864
 
859
 
create_tab(I) ->
860
 
    {value, {name, Name}} = lists:keysearch(name, 1, I),
861
 
    {value, {type, Type}} = lists:keysearch(type, 1, I),
862
 
    {value, {protection, P}} = lists:keysearch(protection, 1, I),
863
 
    {value, {named_table, Val}} = lists:keysearch(named_table, 1, I),
864
 
    {value, {keypos, Kp}} = lists:keysearch(keypos, 1, I),
865
 
    {value, {size, Sz}} = lists:keysearch(size, 1, I),
866
 
    try
867
 
        Tab = ets:new(Name, [Type, P, {keypos, Kp} | named_table(Val)]),
868
 
        {ok, Tab, Sz}
869
 
    catch
870
 
        _:_ ->
871
 
            throw(cannot_create_table)
 
865
create_tab(I, TabArg) ->
 
866
    {name, Name} = lists:keyfind(name, 1, I),
 
867
    {type, Type} = lists:keyfind(type, 1, I),
 
868
    {protection, P} = lists:keyfind(protection, 1, I),
 
869
    {named_table, Val} = lists:keyfind(named_table, 1, I),
 
870
    {keypos, _Kp} = Keypos = lists:keyfind(keypos, 1, I),
 
871
    {size, Sz} = lists:keyfind(size, 1, I),
 
872
    Comp = case lists:keyfind(compressed, 1, I) of
 
873
        {compressed, true} -> [compressed];
 
874
        {compressed, false} -> [];
 
875
        false -> []
 
876
    end,
 
877
    case TabArg of
 
878
        [] ->
 
879
            try
 
880
                Tab = ets:new(Name, [Type, P, Keypos] ++ named_table(Val) ++ Comp),
 
881
                {ok, Tab, Sz}
 
882
            catch _:_ ->
 
883
                throw(cannot_create_table)
 
884
            end;
 
885
        _ ->
 
886
            {ok, TabArg, Sz}
872
887
    end.
873
888
 
874
889
named_table(true) -> [named_table];
905
920
        {value, Val} = lists:keysearch(named_table, 1, FullHeader),
906
921
        {value, Kp} = lists:keysearch(keypos, 1, FullHeader),
907
922
        {value, Sz} = lists:keysearch(size, 1, FullHeader),
908
 
        Ei = case lists:keysearch(extended_info, 1, FullHeader) of
909
 
                 {value, Ei0} -> Ei0;
910
 
                 _ -> {extended_info, []}
 
923
        Ei = case lists:keyfind(extended_info, 1, FullHeader) of
 
924
                 false -> {extended_info, []};
 
925
                 Ei0 -> Ei0
911
926
             end,
912
927
        {ok, [N,Type,P,Val,Kp,Sz,Ei,{version,{Major,Minor}}]}
913
928
    catch
1021
1036
    options([Option], Keys, []).
1022
1037
 
1023
1038
options(Options, [Key | Keys], L) when is_list(Options) ->
1024
 
    V = case lists:keysearch(Key, 1, Options) of
1025
 
            {value, {n_objects, default}} ->
 
1039
    V = case lists:keyfind(Key, 1, Options) of
 
1040
            {n_objects, default} ->
1026
1041
                {ok, default_option(Key)};
1027
 
            {value, {n_objects, NObjs}} when is_integer(NObjs),
1028
 
                                             NObjs >= 1 ->
 
1042
            {n_objects, NObjs} when is_integer(NObjs), NObjs >= 1 ->
1029
1043
                {ok, NObjs};
1030
 
            {value, {traverse, select}} ->
 
1044
            {traverse, select} ->
1031
1045
                {ok, select};
1032
 
            {value, {traverse, {select, MS}}} ->
1033
 
                {ok, {select, MS}};
1034
 
            {value, {traverse, first_next}} ->
 
1046
            {traverse, {select, _MS} = Select} ->
 
1047
                {ok, Select};
 
1048
            {traverse, first_next} ->
1035
1049
                {ok, first_next};
1036
 
            {value, {traverse, last_prev}} ->
 
1050
            {traverse, last_prev} ->
1037
1051
                {ok, last_prev};
1038
 
            {value, {Key, _}} ->
 
1052
            {Key, _} ->
1039
1053
                badarg;
1040
1054
            false ->
1041
1055
                Default = default_option(Key),