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

« back to all changes in this revision

Viewing changes to lib/stdlib/test/ets_SUITE.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-2011. 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_SUITE).
20
20
 
21
 
-export([all/1]).
22
 
-export([new/1,default/1,setbag/1,badnew/1,verybadnew/1,named/1,keypos2/1,
 
21
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
22
         init_per_group/2,end_per_group/2]).
 
23
-export([default/1,setbag/1,badnew/1,verybadnew/1,named/1,keypos2/1,
23
24
         privacy/1,privacy_owner/2]).
24
 
-export([insert/1,empty/1,badinsert/1]).
25
 
-export([lookup/1,time_lookup/1,badlookup/1,lookup_order/1]).
26
 
-export([delete/1,delete_elem/1,delete_tab/1,delete_large_tab/1,
 
25
-export([empty/1,badinsert/1]).
 
26
-export([time_lookup/1,badlookup/1,lookup_order/1]).
 
27
-export([delete_elem/1,delete_tab/1,delete_large_tab/1,
27
28
         delete_large_named_table/1,
28
29
         evil_delete/1,baddelete/1,match_delete/1,table_leak/1]).
29
30
-export([match_delete3/1]).
30
31
-export([firstnext/1,firstnext_concurrent/1]).
31
32
-export([slot/1]).
32
 
-export([match/1, match1/1, match2/1, match_object/1, match_object2/1]).
33
 
-export([misc/1, dups/1, misc1/1, safe_fixtable/1, info/1, tab2list/1]).
34
 
-export([files/1, tab2file/1, tab2file2/1, tab2file3/1, tabfile_ext1/1,
 
33
-export([ match1/1, match2/1, match_object/1, match_object2/1]).
 
34
-export([ dups/1, misc1/1, safe_fixtable/1, info/1, tab2list/1]).
 
35
-export([ tab2file/1, tab2file2/1, tabfile_ext1/1,
35
36
        tabfile_ext2/1, tabfile_ext3/1, tabfile_ext4/1]).
36
 
-export([heavy/1, heavy_lookup/1, heavy_lookup_element/1]).
37
 
-export([lookup_element/1, lookup_element_mult/1]).
38
 
-export([fold/1]).
 
37
-export([ heavy_lookup/1, heavy_lookup_element/1, heavy_concurrent/1]).
 
38
-export([ lookup_element_mult/1]).
 
39
-export([]).
39
40
-export([foldl_ordered/1, foldr_ordered/1, foldl/1, foldr/1, fold_empty/1]).
40
41
-export([t_delete_object/1, t_init_table/1, t_whitebox/1, 
41
42
         t_delete_all_objects/1, t_insert_list/1, t_test_ms/1,
59
60
-export([otp_7665/1]).
60
61
-export([meta_wb/1]).
61
62
-export([grow_shrink/1, grow_pseudo_deleted/1, shrink_pseudo_deleted/1]).
62
 
-export([meta_smp/1,
 
63
-export([
63
64
         meta_lookup_unnamed_read/1, meta_lookup_unnamed_write/1, 
64
65
         meta_lookup_named_read/1, meta_lookup_named_write/1,
65
66
         meta_newdel_unnamed/1, meta_newdel_named/1]).
66
 
-export([smp_insert/1, smp_fixed_delete/1, smp_unfix_fix/1, smp_select_delete/1, otp_8166/1]).
 
67
-export([smp_insert/1, smp_fixed_delete/1, smp_unfix_fix/1, smp_select_delete/1,
 
68
         otp_8166/1, otp_8732/1]).
67
69
-export([exit_large_table_owner/1,
68
70
         exit_many_large_table_owner/1,
69
71
         exit_many_tables_owner/1,
70
72
         exit_many_many_tables_owner/1]).
71
73
-export([write_concurrency/1, heir/1, give_away/1, setopts/1]).
72
 
-export([bad_table/1]).
 
74
-export([bad_table/1, types/1]).
73
75
 
74
 
-export([init_per_testcase/2, fin_per_testcase/2, end_per_suite/1]).
 
76
-export([init_per_testcase/2, end_per_testcase/2]).
75
77
%% Convenience for manual testing
76
78
-export([random_test/0]).
77
79
 
78
80
% internal exports
79
81
-export([dont_make_worse_sub/0, make_better_sub1/0, make_better_sub2/0]).
80
 
-export([t_repair_continuation_do/1, default_do/1, t_bucket_disappears_do/1,
 
82
-export([t_repair_continuation_do/1, t_bucket_disappears_do/1,
81
83
         select_fail_do/1, whitebox_1/1, whitebox_2/1, t_delete_all_objects_do/1,
82
84
         t_delete_object_do/1, t_init_table_do/1, t_insert_list_do/1,
83
85
         update_element_opts/1, update_element_opts/4, update_element/4, update_element_do/4,
89
91
         match_delete_do/1, match_delete3_do/1, firstnext_do/1, 
90
92
         slot_do/1, match1_do/1, match2_do/1, match_object_do/1, match_object2_do/1,
91
93
         misc1_do/1, safe_fixtable_do/1, info_do/1, dups_do/1, heavy_lookup_do/1,
92
 
         heavy_lookup_element_do/1, member_do/1, otp_5340_do/1, otp_7665_do/1, meta_wb_do/1
 
94
         heavy_lookup_element_do/1, member_do/1, otp_5340_do/1, otp_7665_do/1, meta_wb_do/1,
 
95
         do_heavy_concurrent/1, tab2file2_do/2, exit_large_table_owner_do/2,
 
96
         types_do/1, sleeper/0, rpc_externals/0, memory_do/1,
 
97
         ms_tracee_dummy/1, ms_tracee_dummy/2, ms_tracee_dummy/3, ms_tracee_dummy/4
93
98
        ]).
94
99
 
95
 
-include("test_server.hrl").
 
100
-export([t_select_reverse/1]).
 
101
 
 
102
-include_lib("test_server/include/test_server.hrl").
 
103
 
 
104
-define(m(A,B), ?line assert_eq(A,B)).
96
105
 
97
106
init_per_testcase(Case, Config) ->
98
107
    Seed = {S1,S2,S3} = random:seed0(), %now(),
103
112
    Dog=test_server:timetrap(test_server:minutes(20)),
104
113
    [{watchdog, Dog}, {test_case, Case} | Config].
105
114
 
106
 
fin_per_testcase(_Func, Config) ->
 
115
end_per_testcase(_Func, Config) ->
107
116
    Dog=?config(watchdog, Config),
108
117
    wait_for_test_procs(true),
109
118
    test_server:timetrap_cancel(Dog).
110
 
    
 
119
   
 
120
 
 
121
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
122
 
 
123
suite() -> [{ct_hooks,[ts_install_cth]}].
 
124
 
 
125
all() -> 
 
126
    [{group, new}, {group, insert}, {group, lookup},
 
127
     {group, delete}, firstnext, firstnext_concurrent, slot,
 
128
     {group, match}, t_match_spec_run,
 
129
     {group, lookup_element}, {group, misc}, {group, files},
 
130
     {group, heavy}, ordered, ordered_match,
 
131
     interface_equality, fixtable_next, fixtable_insert,
 
132
     rename, rename_unnamed, evil_rename, update_element,
 
133
     update_counter, evil_update_counter, partly_bound,
 
134
     match_heavy, {group, fold}, member, t_delete_object,
 
135
     t_init_table, t_whitebox, t_delete_all_objects,
 
136
     t_insert_list, t_test_ms, t_select_delete, t_ets_dets,
 
137
     memory, t_select_reverse, t_bucket_disappears,
 
138
     select_fail, t_insert_new, t_repair_continuation,
 
139
     otp_5340, otp_6338, otp_6842_select_1000, otp_7665,
 
140
     otp_8732, meta_wb, grow_shrink, grow_pseudo_deleted,
 
141
     shrink_pseudo_deleted, {group, meta_smp}, smp_insert,
 
142
     smp_fixed_delete, smp_unfix_fix, smp_select_delete,
 
143
     otp_8166, exit_large_table_owner,
 
144
     exit_many_large_table_owner, exit_many_tables_owner,
 
145
     exit_many_many_tables_owner, write_concurrency, heir,
 
146
     give_away, setopts, bad_table, types].
 
147
 
 
148
groups() -> 
 
149
    [{new, [],
 
150
      [default, setbag, badnew, verybadnew, named, keypos2,
 
151
       privacy]},
 
152
     {insert, [], [empty, badinsert]},
 
153
     {lookup, [], [time_lookup, badlookup, lookup_order]},
 
154
     {lookup_element, [], [lookup_element_mult]},
 
155
     {delete, [],
 
156
      [delete_elem, delete_tab, delete_large_tab,
 
157
       delete_large_named_table, evil_delete, table_leak,
 
158
       baddelete, match_delete, match_delete3]},
 
159
     {match, [],
 
160
      [match1, match2, match_object, match_object2]},
 
161
     {misc, [],
 
162
      [misc1, safe_fixtable, info, dups, tab2list]},
 
163
     {files, [],
 
164
      [tab2file, tab2file2, tabfile_ext1,
 
165
       tabfile_ext2, tabfile_ext3, tabfile_ext4]},
 
166
     {heavy, [],
 
167
      [heavy_lookup, heavy_lookup_element, heavy_concurrent]},
 
168
     {fold, [],
 
169
      [foldl_ordered, foldr_ordered, foldl, foldr,
 
170
       fold_empty]},
 
171
     {meta_smp, [],
 
172
      [meta_lookup_unnamed_read, meta_lookup_unnamed_write,
 
173
       meta_lookup_named_read, meta_lookup_named_write,
 
174
       meta_newdel_unnamed, meta_newdel_named]}].
 
175
 
 
176
init_per_suite(Config) ->
 
177
    Config.
111
178
 
112
179
end_per_suite(_Config) ->
113
180
    stop_spawn_logger(),
114
181
    catch erts_debug:set_internal_state(available_internal_state, false).
115
182
 
116
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
117
 
 
118
 
all(suite) ->
119
 
    [
120
 
     new,insert,lookup,delete,firstnext,firstnext_concurrent,slot,match,
121
 
     t_match_spec_run,
122
 
     lookup_element, misc,files, heavy, 
123
 
     ordered, ordered_match, interface_equality,
124
 
     fixtable_next, fixtable_insert, rename, rename_unnamed, evil_rename,
125
 
     update_element, update_counter, evil_update_counter, partly_bound,
126
 
     match_heavy, fold, member,
127
 
     t_delete_object, t_init_table, t_whitebox, 
128
 
     t_delete_all_objects, t_insert_list, t_test_ms,
129
 
     t_select_delete, t_ets_dets, memory,
130
 
     t_bucket_disappears,
131
 
     select_fail,t_insert_new, t_repair_continuation, otp_5340, otp_6338,
132
 
     otp_6842_select_1000, otp_7665,
133
 
     meta_wb,
134
 
     grow_shrink, grow_pseudo_deleted, shrink_pseudo_deleted,
135
 
     meta_smp,
136
 
     smp_insert, smp_fixed_delete, smp_unfix_fix, smp_select_delete, otp_8166,
137
 
     exit_large_table_owner,
138
 
     exit_many_large_table_owner,
139
 
     exit_many_tables_owner,
140
 
     exit_many_many_tables_owner,
141
 
     write_concurrency, heir, give_away, setopts,
142
 
     bad_table
143
 
    ].
 
183
init_per_group(_GroupName, Config) ->
 
184
        Config.
 
185
 
 
186
end_per_group(_GroupName, Config) ->
 
187
        Config.
 
188
 
144
189
 
145
190
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
146
191
 
153
198
 
154
199
t_bucket_disappears_do(Opts) ->
155
200
    ?line EtsMem = etsmem(),
156
 
    ?line ets:new(abcd, [named_table, public, {keypos, 2} | Opts]),
 
201
    ?line ets_new(abcd, [named_table, public, {keypos, 2} | Opts]),
157
202
    ?line ets:insert(abcd, {abcd,1,2}),
158
203
    ?line ets:insert(abcd, {abcd,2,2}),
159
204
    ?line ets:insert(abcd, {abcd,3,2}),
171
216
t_match_spec_run(doc) ->
172
217
    ["Check ets:match_spec_run/2."];
173
218
t_match_spec_run(Config) when is_list(Config) ->
 
219
    init_externals(),
174
220
    ?line EtsMem = etsmem(),
175
 
    ?line [2,3] = ets:match_spec_run([{1},{2},{3}],
176
 
                                     ets:match_spec_compile(
177
 
                                       [{{'$1'},[{'>','$1',1}],['$1']}])),
 
221
 
 
222
    t_match_spec_run_test([{1},{2},{3}],
 
223
                          [{{'$1'},[{'>','$1',1}],['$1']}],
 
224
                          [2,3]),
 
225
 
178
226
    ?line Huge = [{X} || X <- lists:seq(1,2500)],
179
227
    ?line L = lists:seq(2476,2500),
180
 
    ?line L = ets:match_spec_run(Huge,
181
 
                                 ets:match_spec_compile(
182
 
                                   [{{'$1'},[{'>','$1',2475}],['$1']}])),
 
228
    t_match_spec_run_test(Huge, [{{'$1'},[{'>','$1',2475}],['$1']}], L),
 
229
 
183
230
    ?line L2 = [{X*16#FFFFFFF} || X <- L],
184
 
    ?line L2 = ets:match_spec_run(Huge,
185
 
                                  ets:match_spec_compile(
186
 
                                    [{{'$1'},
187
 
                                      [{'>','$1',2475}],
188
 
                                      [{{{'*','$1',16#FFFFFFF}}}]}])),
189
 
    ?line [500,1000,1500,2000,2500] = 
190
 
        ets:match_spec_run(Huge,
191
 
                           ets:match_spec_compile(
192
 
                             [{{'$1'},
193
 
                               [{'=:=',{'rem','$1',500},0}],
194
 
                               ['$1']}])),
 
231
    t_match_spec_run_test(Huge,
 
232
                          [{{'$1'}, [{'>','$1',2475}], [{{{'*','$1',16#FFFFFFF}}}]}],
 
233
                          L2),
 
234
 
 
235
    t_match_spec_run_test(Huge, [{{'$1'}, [{'=:=',{'rem','$1',500},0}], ['$1']}],
 
236
                          [500,1000,1500,2000,2500]),
 
237
 
 
238
    %% More matching fun with several match clauses and guards,
 
239
    %% applied to a variety of terms.
 
240
    Fun = fun(Term) ->
 
241
                  CTerm = {const, Term},
 
242
 
 
243
                  N_List = [{Term, "0", "v-element"},
 
244
                            {"=hidden_node", "0", Term},
 
245
                            {"0", Term, Term},
 
246
                            {"something", Term, "something else"},
 
247
                            {"guard and res", Term, 872346},
 
248
                            {Term, {'and',Term,'again'}, 3.14},
 
249
                            {Term, {'and',Term,'again'}, "m&g"},
 
250
                            {Term, {'and',Term,'again'}, "m&g&r"},
 
251
                            {[{second,Term}, 'and', "tail"], Term, ['and',"tail"]}],
 
252
 
 
253
                  N_MS = [{{'$1','$2','$3'},
 
254
                           [{'=:=','$1',CTerm}, {'=:=','$2',{const,"0"}}],
 
255
                           [{{"Guard only for $1",'$3'}}]},
 
256
 
 
257
                          {{'$3','$1','$4'},
 
258
                           [{'=:=','$3',"=hidden_node"}, {'=:=','$1',{const,"0"}}],
 
259
                           [{{"Result only for $4",'$4'}}]},
 
260
 
 
261
                          {{'$2','$1','$1'},
 
262
                           [{'=:=','$2',{const,"0"}}],
 
263
                           [{{"Match only for $1",'$2'}}]},
 
264
 
 
265
                          {{'$2',Term,['$3'|'_']},
 
266
                           [{is_list,'$2'},{'=:=','$3',$s}],
 
267
                           [{{"Matching term",'$2'}}]},
 
268
 
 
269
                          {{'$1','$2',872346},
 
270
                           [{'=:=','$2',CTerm}, {is_list,'$1'}],
 
271
                           [{{"Guard and result",'$2'}}]},
 
272
 
 
273
                          {{'$1', {'and','$1','again'}, '$2'},
 
274
                           [{is_float,'$2'}],
 
275
                           [{{"Match and result",'$1'}}]},
 
276
 
 
277
                          {{'$1', {'and','$1','again'}, '$2'},
 
278
                           [{'=:=','$1',CTerm}, {'=:=', '$2', "m&g"}],
 
279
                           [{{"Match and guard",'$2'}}]},
 
280
 
 
281
                          {{'$1', {'and','$1','again'}, "m&g&r"},
 
282
                           [{'=:=','$1',CTerm}],
 
283
                           [{{"Match, guard and result",'$1'}}]},
 
284
 
 
285
                          {{'$1', '$2', '$3'},
 
286
                           [{'=:=','$1',[{{second,'$2'}} | '$3']}],
 
287
                           [{{"Building guard"}}]}
 
288
                         ],
 
289
 
 
290
                  N_Result = [{"Guard only for $1", "v-element"},
 
291
                              {"Result only for $4", Term},
 
292
                              {"Match only for $1", "0"},
 
293
                              {"Matching term","something"},
 
294
                              {"Guard and result",Term},
 
295
                              {"Match and result",Term},
 
296
                              {"Match and guard","m&g"},
 
297
                              {"Match, guard and result",Term},
 
298
                              {"Building guard"}],
 
299
 
 
300
                  F = fun(N_MS_Perm) ->
 
301
                              t_match_spec_run_test(N_List, N_MS_Perm, N_Result)
 
302
                      end,
 
303
                  repeat_for_permutations(F, N_MS)
 
304
          end,
 
305
 
 
306
    test_terms(Fun, skip_refc_check),
 
307
 
195
308
    ?line verify_etsmem(EtsMem).
196
309
 
 
310
t_match_spec_run_test(List, MS, Result) ->
 
311
 
 
312
    %%io:format("ms = ~p\n",[MS]),
 
313
 
 
314
    ?m(Result, ets:match_spec_run(List, ets:match_spec_compile(MS))),
 
315
 
 
316
    %% Check that ets:select agree
 
317
    Tab = ets:new(xxx, [bag]),
 
318
    ets:insert(Tab, List),
 
319
    SRes = lists:sort(Result),
 
320
    ?m(SRes, lists:sort(ets:select(Tab, MS))),
 
321
    ets:delete(Tab),
 
322
 
 
323
    %% Check that tracing agree
 
324
    Self = self(),
 
325
    {Tracee, MonRef} = spawn_monitor(fun() -> ms_tracee(Self, List) end),
 
326
    receive {Tracee, ready} -> ok end,
 
327
 
 
328
    MST = lists:map(fun(Clause) -> ms_clause_ets_to_trace(Clause) end, MS),
 
329
 
 
330
    %%io:format("MS = ~p\nMST= ~p\n",[MS,MST]),
 
331
 
 
332
    erlang:trace_pattern({?MODULE,ms_tracee_dummy,'_'}, MST , [local]),
 
333
    erlang:trace(Tracee, true, [call]),
 
334
    Tracee ! start,
 
335
    TRes = ms_tracer_collect(Tracee, MonRef, []),
 
336
    %erlang:trace(Tracee, false, [call]),
 
337
    %Tracee ! stop,
 
338
    case TRes of
 
339
        SRes -> ok;
 
340
        _ ->
 
341
            io:format("TRACE MATCH FAILED\n"),
 
342
            io:format("Input = ~p\nMST = ~p\nExpected = ~p\nGot = ~p\n", [List, MST, SRes, TRes]),
 
343
            ?t:fail("TRACE MATCH FAILED")
 
344
    end,
 
345
    ok.
 
346
 
 
347
 
 
348
 
 
349
ms_tracer_collect(Tracee, Ref, Acc) ->
 
350
    receive
 
351
        {trace, Tracee, call, _Args, [Msg]} ->
 
352
            %io:format("trace Args=~p  Msg=~p\n", [_Args, Msg]),
 
353
            ms_tracer_collect(Tracee, Ref, [Msg | Acc]);
 
354
 
 
355
        {'DOWN', Ref, process, Tracee, _} ->
 
356
            %io:format("monitor DOWN for ~p\n", [Tracee]),
 
357
            TDRef = erlang:trace_delivered(Tracee),
 
358
            ms_tracer_collect(Tracee, TDRef, Acc);
 
359
 
 
360
        {trace_delivered, Tracee, Ref} ->
 
361
            %%io:format("trace delivered for ~p\n", [Tracee]),
 
362
            lists:sort(Acc);
 
363
 
 
364
        Other ->
 
365
            io:format("Unexpected message = ~p\n", [Other]),
 
366
            ?t:fail("Unexpected tracer msg")
 
367
    end.
 
368
 
 
369
 
 
370
ms_tracee(Parent, CallArgList) ->
 
371
    %io:format("ms_tracee ~p started with ArgList = ~p\n", [self(), CallArgList]),
 
372
    Parent ! {self(), ready},
 
373
    receive start -> ok end,
 
374
    lists:foreach(fun(Args) ->
 
375
                          erlang:apply(?MODULE, ms_tracee_dummy, tuple_to_list(Args))
 
376
                  end, CallArgList).
 
377
    %%receive stop -> ok end.
 
378
 
 
379
 
 
380
 
 
381
ms_tracee_dummy(_) -> ok.
 
382
ms_tracee_dummy(_,_) -> ok.
 
383
ms_tracee_dummy(_,_,_) -> ok.
 
384
ms_tracee_dummy(_,_,_,_) -> ok.
 
385
 
 
386
ms_clause_ets_to_trace({Head, Guard, Body}) ->
 
387
    {tuple_to_list(Head), Guard, [{message, Body}]}.
 
388
 
 
389
assert_eq(A,A) -> ok;
 
390
assert_eq(A,B) ->
 
391
    io:format("FAILED MATCH:\n~p\n =/=\n~p\n",[A,B]),
 
392
    ?t:fail("assert_eq failed").
197
393
 
198
394
 
199
395
t_repair_continuation(suite) -> 
209
405
    ?line MS = [{'_',[],[true]}],
210
406
    ?line MS2 = [{{{'$1','_'},'_'},[],['$1']}],
211
407
    (fun() ->
212
 
             ?line T = ets:new(x,[ordered_set|Opts]),
 
408
             ?line T = ets_new(x,[ordered_set|Opts]),
213
409
             ?line F = fun(0,_)->ok;(N,F) -> ets:insert(T,{N,N}), F(N-1,F) end,
214
410
             ?line F(1000,F),
215
411
             ?line {_,C} = ets:select(T,MS,5),
221
417
             ?line true = ets:delete(T)
222
418
     end)(),
223
419
    (fun() ->
224
 
             ?line T = ets:new(x,[ordered_set|Opts]),
 
420
             ?line T = ets_new(x,[ordered_set|Opts]),
225
421
             ?line F = fun(0,_)->ok;(N,F) -> ets:insert(T,{N,N}), F(N-1,F) end,
226
422
             ?line F(1000,F),
227
423
             ?line {_,C} = ets:select(T,MS,1001),
233
429
     end)(),
234
430
    
235
431
    (fun() ->
236
 
             ?line T = ets:new(x,[ordered_set|Opts]),
 
432
             ?line T = ets_new(x,[ordered_set|Opts]),
237
433
             ?line F = fun(0,_)->ok;(N,F) -> 
238
434
                               ets:insert(T,{integer_to_list(N),N}), 
239
435
                               F(N-1,F) 
248
444
             ?line true = ets:delete(T)
249
445
     end)(),
250
446
    (fun() ->
251
 
             ?line T = ets:new(x,[ordered_set|Opts]),
 
447
             ?line T = ets_new(x,[ordered_set|Opts]),
252
448
             ?line F = fun(0,_)->ok;(N,F) -> 
253
449
                               ets:insert(T,{{integer_to_list(N),N},N}), 
254
450
                               F(N-1,F) 
264
460
     end)(),
265
461
    
266
462
    (fun() ->
267
 
             ?line T = ets:new(x,[set|Opts]),
 
463
             ?line T = ets_new(x,[set|Opts]),
268
464
             ?line F = fun(0,_)->ok;(N,F) -> 
269
465
                               ets:insert(T,{N,N}), 
270
466
                               F(N-1,F) 
279
475
             ?line true = ets:delete(T)
280
476
     end)(),
281
477
    (fun() ->
282
 
             ?line T = ets:new(x,[set|Opts]),
283
 
             ?line F = fun(0,_)->ok;(N,F) -> 
284
 
                               ets:insert(T,{integer_to_list(N),N}), 
285
 
                               F(N-1,F) 
286
 
                       end,
287
 
             ?line F(1000,F),
288
 
             ?line {_,C} = ets:select(T,MS,5),
289
 
             ?line C2 = erlang:setelement(4,C,<<>>),
290
 
             ?line {'EXIT',{badarg,_}} = (catch ets:select(C2)),
291
 
             ?line C3 = ets:repair_continuation(C2,MS),
292
 
             ?line {[true,true,true,true,true],_} = ets:select(C3),
293
 
             ?line {[true,true,true,true,true],_} = ets:select(C),
294
 
             ?line true = ets:delete(T)
295
 
     end)(),
296
 
    (fun() ->
297
 
             ?line T = ets:new(x,[bag|Opts]),
298
 
             ?line F = fun(0,_)->ok;(N,F) -> 
299
 
                               ets:insert(T,{integer_to_list(N),N}), 
300
 
                               F(N-1,F) 
301
 
                       end,
302
 
             ?line F(1000,F),
303
 
             ?line {_,C} = ets:select(T,MS,5),
304
 
             ?line C2 = erlang:setelement(4,C,<<>>),
305
 
             ?line {'EXIT',{badarg,_}} = (catch ets:select(C2)),
306
 
             ?line C3 = ets:repair_continuation(C2,MS),
307
 
             ?line {[true,true,true,true,true],_} = ets:select(C3),
308
 
             ?line {[true,true,true,true,true],_} = ets:select(C),
309
 
             ?line true = ets:delete(T)
310
 
     end)(),
311
 
    (fun() ->
312
 
             ?line T = ets:new(x,[duplicate_bag|Opts]),
 
478
             ?line T = ets_new(x,[set|Opts]),
 
479
             ?line F = fun(0,_)->ok;(N,F) -> 
 
480
                               ets:insert(T,{integer_to_list(N),N}), 
 
481
                               F(N-1,F) 
 
482
                       end,
 
483
             ?line F(1000,F),
 
484
             ?line {_,C} = ets:select(T,MS,5),
 
485
             ?line C2 = erlang:setelement(4,C,<<>>),
 
486
             ?line {'EXIT',{badarg,_}} = (catch ets:select(C2)),
 
487
             ?line C3 = ets:repair_continuation(C2,MS),
 
488
             ?line {[true,true,true,true,true],_} = ets:select(C3),
 
489
             ?line {[true,true,true,true,true],_} = ets:select(C),
 
490
             ?line true = ets:delete(T)
 
491
     end)(),
 
492
    (fun() ->
 
493
             ?line T = ets_new(x,[bag|Opts]),
 
494
             ?line F = fun(0,_)->ok;(N,F) -> 
 
495
                               ets:insert(T,{integer_to_list(N),N}), 
 
496
                               F(N-1,F) 
 
497
                       end,
 
498
             ?line F(1000,F),
 
499
             ?line {_,C} = ets:select(T,MS,5),
 
500
             ?line C2 = erlang:setelement(4,C,<<>>),
 
501
             ?line {'EXIT',{badarg,_}} = (catch ets:select(C2)),
 
502
             ?line C3 = ets:repair_continuation(C2,MS),
 
503
             ?line {[true,true,true,true,true],_} = ets:select(C3),
 
504
             ?line {[true,true,true,true,true],_} = ets:select(C),
 
505
             ?line true = ets:delete(T)
 
506
     end)(),
 
507
    (fun() ->
 
508
             ?line T = ets_new(x,[duplicate_bag|Opts]),
313
509
             ?line F = fun(0,_)->ok;(N,F) -> 
314
510
                               ets:insert(T,{integer_to_list(N),N}), 
315
511
                               F(N-1,F) 
327
523
    ?line true = ets:is_compiled_ms(ets:match_spec_compile(MS)),
328
524
    ?line verify_etsmem(EtsMem).
329
525
 
330
 
new(suite) -> [default,setbag,badnew,verybadnew,named,keypos2,privacy].
331
526
 
332
527
default(doc) ->
333
 
    ["Test case to check that a new ets table is defined as a `set' and "
334
 
     "`protected'"];
 
528
    ["Check correct default vaules of a new ets table"];
335
529
default(suite) -> [];
336
530
default(Config) when is_list(Config) ->
337
531
    %% Default should be set,protected
338
 
    repeat_for_opts(default_do).
339
 
 
340
 
default_do(Opts) ->
341
532
    ?line EtsMem = etsmem(),
342
 
    ?line Def = ets:new(def,Opts),
 
533
    ?line Def = ets_new(def,[]),
343
534
    ?line set = ets:info(Def,type),
344
535
    ?line protected = ets:info(Def,protection),
 
536
    Compressed = erlang:system_info(ets_always_compress),
 
537
    ?line Compressed = ets:info(Def,compressed),
 
538
    Self = self(),
 
539
    ?line Self = ets:info(Def,owner),
 
540
    ?line none = ets:info(Def, heir),
 
541
    ?line false = ets:info(Def,named_table),
345
542
    ?line ets:delete(Def),
346
543
    ?line verify_etsmem(EtsMem).
347
544
 
355
552
    ?line verify_etsmem(EtsMem).
356
553
 
357
554
select_fail_do(Opts) ->
358
 
    ?line T = ets:new(x,Opts),
 
555
    ?line T = ets_new(x,Opts),
359
556
    ?line ets:insert(T,{a,a}),
360
557
    ?line case (catch 
361
558
                    ets:select(T,[{{a,'_'},[],[{snuffla}]}])) of
378
575
 
379
576
-define(S(T),ets:info(T,memory)).
380
577
-define(TAB_STRUCT_SZ, erts_debug:get_internal_state('DbTable_words')).
381
 
-define(NORMAL_TAB_STRUCT_SZ, 26). %% SunOS5.8, 32-bit, non smp, private heap
 
578
%%-define(NORMAL_TAB_STRUCT_SZ, 26). %% SunOS5.8, 32-bit, non smp, private heap
382
579
%%
383
580
%% The hardcoded expected memory sizes (in words) are the ones we expect on:
384
581
%%   SunOS5.8, 32-bit, non smp, private heap
385
582
%%
386
 
memory(doc) ->
387
 
    ["Whitebox test of ets:info(X,memory)"];
388
 
memory(suite) ->
389
 
    [];
 
583
memory(doc) -> ["Whitebox test of ets:info(X,memory)"];
 
584
memory(suite) -> [];
390
585
memory(Config) when is_list(Config) ->
391
586
    ?line erts_debug:set_internal_state(available_internal_state, true),
392
587
    ?line ok = chk_normal_tab_struct_size(),
393
 
    ?line L = [T1,T2,T3,T4] = fill_sets_int(1000),
394
 
    ?line XRes1 = adjust_xmem(L, {16862,16072,16072,16078}),
 
588
    repeat_for_opts(memory_do,[compressed]),
 
589
    ?line catch erts_debug:set_internal_state(available_internal_state, false).
 
590
 
 
591
memory_do(Opts) ->
 
592
    ?line L = [T1,T2,T3,T4] = fill_sets_int(1000,Opts),
 
593
    XR1 = case mem_mode(T1) of
 
594
            {normal,_} ->     {13836,13046,13046,13052}; %{13862,13072,13072,13078};
 
595
            {compressed,4} -> {11041,10251,10251,10252}; %{11067,10277,10277,10278};
 
596
            {compressed,8} -> {10050,9260,9260,9260} %{10076,9286,9286,9286}
 
597
          end,
 
598
    ?line XRes1 = adjust_xmem(L, XR1),
395
599
    ?line Res1 = {?S(T1),?S(T2),?S(T3),?S(T4)},
396
600
    ?line lists:foreach(fun(T) ->
397
601
                                Before = ets:info(T,size),
402
606
                                          [Key, ets:info(T,type), Before, ets:info(T,size), Objs])
403
607
                  end,
404
608
                  L),
405
 
    ?line XRes2 = adjust_xmem(L, {16849,16060,16048,16054}),
 
609
    XR2 = case mem_mode(T1) of
 
610
            {normal,_} ->     {13826,13037,13028,13034}; %{13852,13063,13054,13060};
 
611
            {compressed,4} -> {11031,10242,10233,10234}; %{11057,10268,10259,10260};
 
612
            {compressed,8} -> {10040,9251,9242,9242}     %10066,9277,9268,9268}
 
613
          end,
 
614
    ?line XRes2 = adjust_xmem(L, XR2),
406
615
    ?line Res2 = {?S(T1),?S(T2),?S(T3),?S(T4)},
407
616
    ?line lists:foreach(fun(T) ->
408
617
                                Before = ets:info(T,size),
413
622
                                          [Key, ets:info(T,type), Before, ets:info(T,size), Objs])
414
623
                        end,
415
624
                        L),
416
 
    ?line XRes3 = adjust_xmem(L, {16836,16048,16024,16030}),
 
625
    XR3 = case mem_mode(T1) of
 
626
                {normal,_} ->     {13816,13028,13010,13016}; %{13842,13054,13036,13042};
 
627
                {compressed,4} -> {11021,10233,10215,10216}; %{11047,10259,10241,10242};
 
628
                {compressed,8} -> {10030,9242,9224,9224} %{10056,9268,9250,9250}
 
629
          end,
 
630
    ?line XRes3 = adjust_xmem(L, XR3),
417
631
    ?line Res3 = {?S(T1),?S(T2),?S(T3),?S(T4)},
418
632
    ?line lists:foreach(fun(T) ->
419
633
                          ?line ets:delete_all_objects(T)
420
634
                  end,
421
635
                  L),
422
 
    ?line XRes4 = adjust_xmem(L, {76,286,286,286}),
 
636
    ?line XRes4 = adjust_xmem(L, {50,260,260,260}), %{76,286,286,286}),
423
637
    ?line Res4 = {?S(T1),?S(T2),?S(T3),?S(T4)},
424
638
    lists:foreach(fun(T) ->
425
639
                          ?line ets:delete(T)
430
644
                          ?line ets:select_delete(T,[{'_',[],[true]}])
431
645
                  end,
432
646
                  L2),
433
 
    ?line XRes5 = adjust_xmem(L2, {76,286,286,286}),
 
647
    ?line XRes5 = adjust_xmem(L2, {50,260,260,260}), %{76,286,286,286}),
434
648
    ?line Res5 = {?S(T11),?S(T12),?S(T13),?S(T14)},
435
 
    ?line ?t:format("XRes1 = ~p~n"
 
649
    ?line io:format("XRes1 = ~p~n"
436
650
                    " Res1 = ~p~n~n"
437
651
                    "XRes2 = ~p~n"
438
652
                    " Res2 = ~p~n~n"
452
666
    ?line XRes3 = Res3,
453
667
    ?line XRes4 = Res4,
454
668
    ?line XRes5 = Res5,
455
 
    ?line catch erts_debug:set_internal_state(available_internal_state, false),
456
669
    ?line ok.
457
670
 
 
671
mem_mode(T) ->
 
672
    {case ets:info(T,compressed) of
 
673
        true -> compressed;
 
674
        false -> normal
 
675
     end,
 
676
     erlang:system_info(wordsize)}.
 
677
 
458
678
chk_normal_tab_struct_size() ->
459
679
    ?line System = {os:type(),
460
680
                    os:version(),
462
682
                    erlang:system_info(smp_support),
463
683
                    erlang:system_info(heap_type)},
464
684
    ?line ?t:format("System = ~p~n", [System]),
465
 
    ?line ?t:format("?NORMAL_TAB_STRUCT_SZ=~p~n", [?NORMAL_TAB_STRUCT_SZ]),
 
685
    %%?line ?t:format("?NORMAL_TAB_STRUCT_SZ=~p~n", [?NORMAL_TAB_STRUCT_SZ]),
466
686
    ?line ?t:format("?TAB_STRUCT_SZ=~p~n", [?TAB_STRUCT_SZ]),
467
 
    ?line case System of
468
 
              {{unix, sunos}, {5, 8, 0}, 4, false, private} ->
469
 
                  ?line ?NORMAL_TAB_STRUCT_SZ = ?TAB_STRUCT_SZ,
470
 
                  ?line ok;
471
 
              _ ->
472
 
                  ?line ok
473
 
          end.
474
 
 
475
 
adjust_xmem([T1,T2,T3,T4], {A0,B0,C0,D0} = Mem0) ->
 
687
    ok.
 
688
%   ?line case System of
 
689
%             {{unix, sunos}, {5, 8, 0}, 4, false, private} ->
 
690
%                 ?line ?NORMAL_TAB_STRUCT_SZ = ?TAB_STRUCT_SZ,
 
691
%                 ?line ok;
 
692
%             _ ->
 
693
%                 ?line ok
 
694
%         end.
 
695
 
 
696
-define(DB_TREE_STACK_NEED,50). % The static stack for a tree, in halfword pointers are two internal words
 
697
                                % so the stack gets twice as big
 
698
-define(DB_HASH_SIZEOF_EXTSEG,260). % The segment size in words, in halfword this will be twice as large.
 
699
 
 
700
adjust_xmem([T1,T2,T3,T4], {A0,B0,C0,D0} = _Mem0) ->
476
701
    %% Adjust for 64-bit, smp, and os:
477
702
    %%   Table struct size may differ.
478
 
    Mem1 = case ?TAB_STRUCT_SZ of
479
 
               ?NORMAL_TAB_STRUCT_SZ ->
480
 
                   Mem0;
481
 
               TabStructSz ->
482
 
                   TabDiff = TabStructSz - ?NORMAL_TAB_STRUCT_SZ,
483
 
                   {A0+TabDiff, B0+TabDiff, C0+TabDiff, D0+TabDiff}
484
 
           end,
 
703
 
 
704
%   Mem1 = case ?TAB_STRUCT_SZ of
 
705
%              ?NORMAL_TAB_STRUCT_SZ ->
 
706
%                  Mem0;
 
707
%              TabStructSz ->
 
708
%                  TabDiff = TabStructSz - ?NORMAL_TAB_STRUCT_SZ,
 
709
%                  {A0+TabDiff, B0+TabDiff, C0+TabDiff, D0+TabDiff}
 
710
%          end,
 
711
 
 
712
    TabDiff = ?TAB_STRUCT_SZ,
 
713
    Mem1 = {A0+TabDiff, B0+TabDiff, C0+TabDiff, D0+TabDiff},
 
714
 
 
715
    Mem2 = case {erlang:system_info({wordsize,internal}),erlang:system_info({wordsize,external})} of
 
716
                 %% Halfword, corrections for regular pointers occupying two internal words.
 
717
                 {4,8} ->
 
718
                        {A1,B1,C1,D1} = Mem1,
 
719
                        {A1+4*ets:info(T1, size)+?DB_TREE_STACK_NEED,
 
720
                         B1+3*ets:info(T2, size)+?DB_HASH_SIZEOF_EXTSEG,
 
721
                         C1+3*ets:info(T3, size)+?DB_HASH_SIZEOF_EXTSEG,
 
722
                         D1+3*ets:info(T4, size)+?DB_HASH_SIZEOF_EXTSEG};
 
723
                 _ ->
 
724
                        Mem1
 
725
                end,
 
726
 
485
727
    %% Adjust for hybrid and shared heaps:
486
728
    %%   Each record is one word smaller.
487
 
    Mem2 = case erlang:system_info(heap_type) of
488
 
               private ->
489
 
                   Mem1;
490
 
               _ ->
491
 
                   {A1,B1,C1,D1} = Mem1,
492
 
                   {A1-ets:info(T1, size),B1-ets:info(T2, size),
493
 
                    C1-ets:info(T3, size),D1-ets:info(T4, size)}
494
 
           end,
 
729
    %%Mem2 = case erlang:system_info(heap_type) of
 
730
    %%             private ->
 
731
    %%                 Mem1;
 
732
    %%             _ ->
 
733
    %%                 {A1,B1,C1,D1} = Mem1,
 
734
    %%                 {A1-ets:info(T1, size),B1-ets:info(T2, size),
 
735
    %%                  C1-ets:info(T3, size),D1-ets:info(T4, size)}
 
736
    %%          end,
495
737
    %%{Mem2,{ets:info(T1,stats),ets:info(T2,stats),ets:info(T3,stats),ets:info(T4,stats)}}.
496
738
    Mem2.
497
739
 
510
752
    ?line verify_etsmem(EtsMem).
511
753
 
512
754
whitebox_1(Opts) ->
513
 
    ?line T=ets:new(x,[bag | Opts]),
 
755
    ?line T=ets_new(x,[bag | Opts]),
514
756
    ?line ets:insert(T,[{du,glade},{ta,en}]),
515
757
    ?line ets:insert(T,[{hej,hopp2},{du,glade2},{ta,en2}]),
516
758
    ?line {_,C}=ets:match(T,{ta,'$1'},1),
520
762
    ok.
521
763
 
522
764
whitebox_2(Opts) ->
523
 
    ?line T=ets:new(x,[ordered_set, {keypos,2} | Opts]),
524
 
    ?line T2=ets:new(x,[set, {keypos,2}| Opts]),
 
765
    ?line T=ets_new(x,[ordered_set, {keypos,2} | Opts]),
 
766
    ?line T2=ets_new(x,[set, {keypos,2}| Opts]),
525
767
    ?line 0 = ets:select_delete(T,[{{hej},[],[true]}]),
526
768
    ?line 0 = ets:select_delete(T,[{{hej,hopp},[],[true]}]),
527
769
    ?line 0 = ets:select_delete(T2,[{{hej},[],[true]}]),
543
785
    ?line (catch file:delete(Fname)),
544
786
    ?line {ok,DTab} = dets:open_file(testdets_1,
545
787
                               [{file, Fname}]),
546
 
    ?line ETab = ets:new(x,Opts),
 
788
    ?line ETab = ets_new(x,Opts),
547
789
    ?line filltabint(ETab,3000),
548
790
    ?line DTab = ets:to_dets(ETab,DTab),
549
791
    ?line ets:delete_all_objects(ETab),
555
797
        (catch ets:to_dets(ETab,DTab)),
556
798
    ?line {'EXIT',{badarg,[{ets,from_dets,[ETab,DTab]}|_]}} =
557
799
        (catch ets:from_dets(ETab,DTab)),
558
 
    ?line ETab2 = ets:new(x,Opts),
 
800
    ?line ETab2 = ets_new(x,Opts),
559
801
    ?line filltabint(ETab2,3000),
560
802
    ?line dets:close(DTab),
561
803
    ?line {'EXIT',{badarg,[{ets,to_dets,[ETab2,DTab]}|_]}} =
576
818
    ?line verify_etsmem(EtsMem).
577
819
 
578
820
t_delete_all_objects_do(Opts) ->
579
 
    ?line T=ets:new(x,Opts),
 
821
    ?line T=ets_new(x,Opts),
580
822
    ?line filltabint(T,4000),
581
823
    ?line O=ets:first(T),
582
824
    ?line ets:next(T,O),
605
847
    ?line verify_etsmem(EtsMem).
606
848
 
607
849
t_delete_object_do(Opts) ->
608
 
    ?line T = ets:new(x,Opts),
 
850
    ?line T = ets_new(x,Opts),
609
851
    ?line filltabint(T,4000),
610
852
    ?line del_one_by_one_set(T,1,4001),
611
853
    ?line filltabint(T,4000),
622
864
    ?line 3999 = ets:info(T,size),
623
865
    ?line 0 = ets:info(T,kept_objects),
624
866
    ?line ets:delete(T),
625
 
    ?line T1 = ets:new(x,[ordered_set | Opts]),
 
867
    ?line T1 = ets_new(x,[ordered_set | Opts]),
626
868
    ?line filltabint(T1,4000),
627
869
    ?line del_one_by_one_set(T1,1,4001),
628
870
    ?line filltabint(T1,4000),
629
871
    ?line del_one_by_one_set(T1,4000,0),
630
872
    ?line ets:delete(T1),
631
 
    ?line T2 = ets:new(x,[bag | Opts]),
 
873
    ?line T2 = ets_new(x,[bag | Opts]),
632
874
    ?line filltabint2(T2,4000),
633
875
    ?line del_one_by_one_bag(T2,1,4001),
634
876
    ?line filltabint2(T2,4000),
635
877
    ?line del_one_by_one_bag(T2,4000,0),
636
878
    ?line ets:delete(T2),
637
 
    ?line T3 = ets:new(x,[duplicate_bag | Opts]),
 
879
    ?line T3 = ets_new(x,[duplicate_bag | Opts]),
638
880
    ?line filltabint3(T3,4000),
639
881
    ?line del_one_by_one_dbag_1(T3,1,4001),
640
882
    ?line filltabint3(T3,4000),
681
923
    ?line verify_etsmem(EtsMem).
682
924
 
683
925
t_init_table_do(Opts) ->
684
 
    ?line T = ets:new(x,[duplicate_bag | Opts]),
 
926
    ?line T = ets_new(x,[duplicate_bag | Opts]),
685
927
    ?line filltabint(T,4000),
686
928
    ?line ets:init_table(T, make_init_fun(1)),
687
929
    ?line del_one_by_one_dbag_1(T,4000,0),
763
1005
    ?line verify_etsmem(EtsMem).
764
1006
 
765
1007
t_insert_list_do(Opts) ->
766
 
    ?line T = ets:new(x,[duplicate_bag | Opts]),
 
1008
    ?line T = ets_new(x,[duplicate_bag | Opts]),
767
1009
    ?line do_fill_dbag_using_lists(T,4000),
768
1010
    ?line del_one_by_one_dbag_2(T,4000,0),
769
1011
    ?line ets:delete(T).
786
1028
    ?line true = (if is_list(String) -> true; true -> false end),
787
1029
    ?line verify_etsmem(EtsMem).
788
1030
 
 
1031
t_select_reverse(doc) ->
 
1032
    ["Test the select reverse BIF's"];
 
1033
t_select_reverse(suite) ->
 
1034
    [];
 
1035
t_select_reverse(Config) when is_list(Config) ->
 
1036
    ?line Table = ets_new(xxx, [ordered_set]),
 
1037
    ?line filltabint(Table,1000),
 
1038
    ?line A = lists:reverse(ets:select(Table,[{{'$1', '_'},
 
1039
                                         [{'>',
 
1040
                                           {'rem',
 
1041
                                            '$1', 5},
 
1042
                                           2}],
 
1043
                                         ['$_']}])),
 
1044
    ?line A = ets:select_reverse(Table,[{{'$1', '_'},
 
1045
                                   [{'>',
 
1046
                                     {'rem',
 
1047
                                      '$1', 5},
 
1048
                                     2}],
 
1049
                                   ['$_']}]),
 
1050
    ?line A = reverse_chunked(Table,[{{'$1', '_'},
 
1051
                                   [{'>',
 
1052
                                     {'rem',
 
1053
                                      '$1', 5},
 
1054
                                     2}],
 
1055
                                   ['$_']}],3),
 
1056
    % A set/bag/duplicate_bag should get the same result regardless
 
1057
    % of select or select_reverse
 
1058
    ?line Table2 = ets_new(xxx, [set]),
 
1059
    ?line filltabint(Table2,1000),
 
1060
    ?line Table3 = ets_new(xxx, [bag]),
 
1061
    ?line filltabint(Table3,1000),
 
1062
    ?line Table4 = ets_new(xxx, [duplicate_bag]),
 
1063
    ?line filltabint(Table4,1000),
 
1064
    ?line lists:map(fun(Tab) ->
 
1065
                      B = ets:select(Tab,[{{'$1', '_'},
 
1066
                                           [{'>',
 
1067
                                             {'rem',
 
1068
                                              '$1', 5},
 
1069
                                             2}],
 
1070
                                           ['$_']}]),
 
1071
                      B = ets:select_reverse(Tab,[{{'$1', '_'},
 
1072
                                                   [{'>',
 
1073
                                                     {'rem',
 
1074
                                                      '$1', 5},
 
1075
                                                     2}],
 
1076
                                                   ['$_']}])
 
1077
              end,[Table2, Table3, Table4]),
 
1078
    ok.
 
1079
 
 
1080
 
 
1081
 
 
1082
reverse_chunked(T,MS,N) ->
 
1083
    do_reverse_chunked(ets:select_reverse(T,MS,N),[]).
 
1084
 
 
1085
do_reverse_chunked('$end_of_table',Acc) ->
 
1086
    lists:reverse(Acc);
 
1087
do_reverse_chunked({L,C},Acc) ->
 
1088
    NewAcc = lists:reverse(L)++Acc,
 
1089
    do_reverse_chunked(ets:select_reverse(C), NewAcc).
 
1090
 
 
1091
 
789
1092
t_select_delete(doc) ->
790
1093
    ["Test the ets:select_delete/2 and ets:select_count/2 BIF's"];
791
1094
t_select_delete(suite) ->
1064
1367
 
1065
1368
do_random_test() ->
1066
1369
    ?line EtsMem = etsmem(),
1067
 
    ?line OrdSet = ets:new(xxx,[ordered_set]),
1068
 
    ?line Set = ets:new(xxx,[]),
 
1370
    ?line OrdSet = ets_new(xxx,[ordered_set]),
 
1371
    ?line Set = ets_new(xxx,[]),
1069
1372
    ?line do_n_times(fun() ->
1070
1373
                       ?line Key = create_random_string(25),
1071
1374
                       ?line Value = create_random_tuple(25),
1269
1572
 
1270
1573
 
1271
1574
update_element_opts(Tuple,KeyPos,UpdPos,Opts) ->
1272
 
    Set = ets:new(set,[{keypos,KeyPos} | Opts]),
1273
 
    OrdSet = ets:new(ordered_set,[ordered_set,{keypos,KeyPos} | Opts]),
 
1575
    Set = ets_new(set,[{keypos,KeyPos} | Opts]),
 
1576
    OrdSet = ets_new(ordered_set,[ordered_set,{keypos,KeyPos} | Opts]),
1274
1577
    update_element(Set,Tuple,KeyPos,UpdPos),
1275
1578
    update_element(OrdSet,Tuple,KeyPos,UpdPos),
1276
1579
    true = ets:delete(Set),
1278
1581
    ok.
1279
1582
 
1280
1583
update_element(T,Tuple,KeyPos,UpdPos) -> 
1281
 
    KeyList = [Key || Key <- lists:seq(1,100)],
 
1584
    KeyList = [17,"seventeen",<<"seventeen">>,{17},list_to_binary(lists:seq(1,100)),make_ref(), self()],
1282
1585
    lists:foreach(fun(Key) -> 
1283
1586
                          TupleWithKey = setelement(KeyPos,Tuple,Key),
1284
1587
                          update_element_do(T,TupleWithKey,Key,UpdPos)
1292
1595
    % This will try all combinations of {fromValue,toValue}
1293
1596
    %
1294
1597
    % IMPORTANT: size(Values) must be a prime number for this to work!!!
 
1598
 
 
1599
    %io:format("update_element_do for key=~p\n",[Key]),
1295
1600
    Big32 = 16#12345678,
1296
1601
    Big64 = 16#123456789abcdef0,
1297
1602
    Values = { 623, -27, 0, Big32, -Big32, Big64, -Big64, Big32*Big32,
1312
1617
                    (ToIx, [], Pos, _Rand, _MeF) ->
1313
1618
                         {Pos, element(ToIx+1,Values)}   % single {pos,value} arg
1314
1619
                 end,
1315
 
                                                
1316
 
    NewTupleF = fun({Pos,Val}, Tpl, _MeF) ->
1317
 
                        setelement(Pos, Tpl, Val);
1318
 
                   ([{Pos,Val} | Tail], Tpl, MeF) ->
1319
 
                        MeF(Tail,setelement(Pos, Tpl, Val),MeF);
1320
 
                   ([], Tpl, _MeF) ->
1321
 
                        Tpl
1322
 
                end,
1323
1620
 
1324
1621
    UpdateF = fun(ToIx,Rand) -> 
1325
1622
                      PosValArg = PosValArgF(ToIx,[],UpdPos,Rand,PosValArgF),
1327
1624
                      ArgHash = erlang:phash2({Tab,Key,PosValArg}),
1328
1625
                      ?line true = ets:update_element(Tab, Key, PosValArg),
1329
1626
                      ?line ArgHash = erlang:phash2({Tab,Key,PosValArg}),
1330
 
                      NewTuple = NewTupleF(PosValArg,Tuple,NewTupleF),
 
1627
                      NewTuple = update_tuple(PosValArg,Tuple),
1331
1628
                      ?line [NewTuple] = ets:lookup(Tab,Key)
1332
1629
              end,
1333
1630
 
1355
1652
    ?line Checksum = (Length-1)*Length*(Length+1) div 2,  % if Length is a prime
1356
1653
    ok.
1357
1654
 
 
1655
update_tuple({Pos,Val}, Tpl) ->
 
1656
    setelement(Pos, Tpl, Val);
 
1657
update_tuple([{Pos,Val} | Tail], Tpl) ->
 
1658
    update_tuple(Tail,setelement(Pos, Tpl, Val));
 
1659
update_tuple([], Tpl) ->
 
1660
    Tpl.
 
1661
 
 
1662
 
 
1663
 
1358
1664
update_element_neg(Opts) ->
1359
 
    Set = ets:new(set,Opts),
1360
 
    OrdSet = ets:new(ordered_set,[ordered_set | Opts]),
 
1665
    Set = ets_new(set,Opts),
 
1666
    OrdSet = ets_new(ordered_set,[ordered_set | Opts]),
1361
1667
    update_element_neg_do(Set),
1362
1668
    update_element_neg_do(OrdSet),
1363
1669
    ets:delete(Set),
1365
1671
    ets:delete(OrdSet),
1366
1672
    ?line {'EXIT',{badarg,_}} = (catch ets:update_element(OrdSet,key,{2,1})),
1367
1673
 
1368
 
    ?line Bag = ets:new(bag,[bag | Opts]),
1369
 
    ?line DBag = ets:new(duplicate_bag,[duplicate_bag | Opts]),
 
1674
    ?line Bag = ets_new(bag,[bag | Opts]),
 
1675
    ?line DBag = ets_new(duplicate_bag,[duplicate_bag | Opts]),
1370
1676
    ?line {'EXIT',{badarg,_}} = (catch ets:update_element(Bag,key,{2,1})),
1371
1677
    ?line {'EXIT',{badarg,_}} = (catch ets:update_element(DBag,key,{2,1})),
1372
1678
    true = ets:delete(Bag),
1416
1722
    ?line verify_etsmem(EtsMem).
1417
1723
 
1418
1724
update_counter_do(Opts) ->
1419
 
    Set = ets:new(set,Opts),
1420
 
    OrdSet = ets:new(ordered_set,[ordered_set | Opts]),
 
1725
    Set = ets_new(set,Opts),
 
1726
    OrdSet = ets_new(ordered_set,[ordered_set | Opts]),
1421
1727
    update_counter_for(Set),
1422
1728
    update_counter_for(OrdSet),
1423
1729
    ets:delete(Set),
1438
1744
                 (Obj, Times, Arg3, Myself) ->
1439
1745
                      ?line {NewObj, Ret} = uc_mimic(Obj,Arg3),
1440
1746
                      ArgHash = erlang:phash2({T,a,Arg3}),
 
1747
                      %%io:format("update_counter(~p, ~p, ~p) expecting ~p\n",[T,a,Arg3,Ret]),
1441
1748
                      ?line Ret = ets:update_counter(T,a,Arg3),
1442
1749
                      ?line ArgHash = erlang:phash2({T,a,Arg3}),
1443
1750
                      %%io:format("NewObj=~p~n ",[NewObj]),
1563
1870
    end.
1564
1871
    
1565
1872
update_counter_neg(Opts) ->
1566
 
    Set = ets:new(set,Opts),
1567
 
    OrdSet = ets:new(ordered_set,[ordered_set | Opts]),
 
1873
    Set = ets_new(set,Opts),
 
1874
    OrdSet = ets_new(ordered_set,[ordered_set | Opts]),
1568
1875
    update_counter_neg_for(Set),
1569
1876
    update_counter_neg_for(OrdSet),
1570
1877
    ets:delete(Set),
1572
1879
    ets:delete(OrdSet),
1573
1880
    ?line {'EXIT',{badarg,_}} = (catch ets:update_counter(OrdSet,key,1)),
1574
1881
 
1575
 
    ?line Bag = ets:new(bag,[bag | Opts]),
1576
 
    ?line DBag = ets:new(duplicate_bag,[duplicate_bag | Opts]),
 
1882
    ?line Bag = ets_new(bag,[bag | Opts]),
 
1883
    ?line DBag = ets_new(duplicate_bag,[duplicate_bag | Opts]),
1577
1884
    ?line {'EXIT',{badarg,_}} = (catch ets:update_counter(Bag,key,1)),
1578
1885
    ?line {'EXIT',{badarg,_}} = (catch ets:update_counter(DBag,key,1)),
1579
1886
    true = ets:delete(Bag),
1646
1953
    end.
1647
1954
 
1648
1955
evil_counter(I,Opts) ->
1649
 
    T = ets:new(a, Opts),
 
1956
    T = ets_new(a, Opts),
1650
1957
    Start0 = case I rem 3 of
1651
1958
                0 -> 16#12345678;
1652
1959
                1 -> 16#12345678FFFFFFFF;
1654
1961
            end,
1655
1962
    Start = Start0 + random:uniform(100000),
1656
1963
    ets:insert(T, {dracula,Start}),
1657
 
    Iter = 90000,
 
1964
    Iter = 40000,
1658
1965
    End = Start + Iter,
1659
1966
    End = evil_counter_1(Iter, T),
1660
1967
    ets:delete(T).
1675
1982
 
1676
1983
fixtable_next_do(Opts) ->
1677
1984
    ?line EtsMem = etsmem(),    
1678
 
    ?line do_fixtable_next(ets:new(set,[public | Opts])),
 
1985
    ?line do_fixtable_next(ets_new(set,[public | Opts])),
1679
1986
    ?line verify_etsmem(EtsMem).
1680
1987
    
1681
1988
do_fixtable_next(Tab) ->
1756
2063
write_concurrency(suite) -> [];
1757
2064
write_concurrency(Config) when is_list(Config) ->
1758
2065
    ?line EtsMem = etsmem(),
1759
 
    Yes1 = ets:new(foo,[public,{write_concurrency,true}]),
1760
 
    Yes2 = ets:new(foo,[protected,{write_concurrency,true}]),
1761
 
    No1 = ets:new(foo,[private,{write_concurrency,true}]),
1762
 
 
1763
 
    Yes3 = ets:new(foo,[bag,public,{write_concurrency,true}]),
1764
 
    Yes4 = ets:new(foo,[bag,protected,{write_concurrency,true}]),
1765
 
    No2 = ets:new(foo,[bag,private,{write_concurrency,true}]),
1766
 
 
1767
 
    Yes5 = ets:new(foo,[duplicate_bag,public,{write_concurrency,true}]),
1768
 
    Yes6 = ets:new(foo,[duplicate_bag,protected,{write_concurrency,true}]),
1769
 
    No3 = ets:new(foo,[duplicate_bag,private,{write_concurrency,true}]),
1770
 
 
1771
 
    No4 = ets:new(foo,[ordered_set,public,{write_concurrency,true}]),
1772
 
    No5 = ets:new(foo,[ordered_set,protected,{write_concurrency,true}]),
1773
 
    No6 = ets:new(foo,[ordered_set,private,{write_concurrency,true}]),
1774
 
 
1775
 
    No7 = ets:new(foo,[public,{write_concurrency,false}]),
1776
 
    No8 = ets:new(foo,[protected,{write_concurrency,false}]),
 
2066
    Yes1 = ets_new(foo,[public,{write_concurrency,true}]),
 
2067
    Yes2 = ets_new(foo,[protected,{write_concurrency,true}]),
 
2068
    No1 = ets_new(foo,[private,{write_concurrency,true}]),
 
2069
 
 
2070
    Yes3 = ets_new(foo,[bag,public,{write_concurrency,true}]),
 
2071
    Yes4 = ets_new(foo,[bag,protected,{write_concurrency,true}]),
 
2072
    No2 = ets_new(foo,[bag,private,{write_concurrency,true}]),
 
2073
 
 
2074
    Yes5 = ets_new(foo,[duplicate_bag,public,{write_concurrency,true}]),
 
2075
    Yes6 = ets_new(foo,[duplicate_bag,protected,{write_concurrency,true}]),
 
2076
    No3 = ets_new(foo,[duplicate_bag,private,{write_concurrency,true}]),
 
2077
 
 
2078
    No4 = ets_new(foo,[ordered_set,public,{write_concurrency,true}]),
 
2079
    No5 = ets_new(foo,[ordered_set,protected,{write_concurrency,true}]),
 
2080
    No6 = ets_new(foo,[ordered_set,private,{write_concurrency,true}]),
 
2081
 
 
2082
    No7 = ets_new(foo,[public,{write_concurrency,false}]),
 
2083
    No8 = ets_new(foo,[protected,{write_concurrency,false}]),
1777
2084
 
1778
2085
    ?line YesMem = ets:info(Yes1,memory),
1779
2086
    ?line NoHashMem = ets:info(No1,memory),
1800
2107
            ?line true = YesMem =:= NoHashMem
1801
2108
    end,
1802
2109
 
1803
 
    ?line {'EXIT',{badarg,_}} = (catch ets:new(foo,[public,{write_concurrency,foo}])),
1804
 
    ?line {'EXIT',{badarg,_}} = (catch ets:new(foo,[public,{write_concurrency}])),
1805
 
    ?line {'EXIT',{badarg,_}} = (catch ets:new(foo,[public,{write_concurrency,true,foo}])),
1806
 
    ?line {'EXIT',{badarg,_}} = (catch ets:new(foo,[public,write_concurrency])),
 
2110
    ?line {'EXIT',{badarg,_}} = (catch ets_new(foo,[public,{write_concurrency,foo}])),
 
2111
    ?line {'EXIT',{badarg,_}} = (catch ets_new(foo,[public,{write_concurrency}])),
 
2112
    ?line {'EXIT',{badarg,_}} = (catch ets_new(foo,[public,{write_concurrency,true,foo}])),
 
2113
    ?line {'EXIT',{badarg,_}} = (catch ets_new(foo,[public,write_concurrency])),
1807
2114
 
1808
2115
    lists:foreach(fun(T) -> ets:delete(T) end,
1809
2116
                  [Yes1,Yes2,Yes3,Yes4,Yes5,Yes6,
1880
2187
                  none -> {heir,none};
1881
2188
                  _ -> {heir, Heir, HeirData}
1882
2189
              end,
1883
 
    ?line T = ets:new(foo,[named_table, private, HeirTpl | Opts]),
 
2190
    ?line T = ets_new(foo,[named_table, private, HeirTpl | Opts]),
1884
2191
    ?line true = ets:insert(T,{key,1}),
1885
2192
    ?line [{key,1}] = ets:lookup(T,key),
1886
2193
    Self = self(),
1952
2259
    repeat_for_opts(give_away_do).
1953
2260
 
1954
2261
give_away_do(Opts) ->
1955
 
    ?line T = ets:new(foo,[named_table, private | Opts]),
 
2262
    ?line T = ets_new(foo,[named_table, private | Opts]),
1956
2263
    ?line true = ets:insert(T,{key,1}),
1957
2264
    ?line [{key,1}] = ets:lookup(T,key),
1958
2265
    Parent = self(),
1978
2285
    ?line undefined = ets:info(T),
1979
2286
 
1980
2287
    %% Give and then kill receiver to get back
1981
 
    ?line T2 = ets:new(foo,[private | Opts]),
 
2288
    ?line T2 = ets_new(foo,[private | Opts]),
1982
2289
    ?line true = ets:insert(T2,{key,1}),
1983
2290
    ?line ets:setopts(T2,{heir,self(),"Som en gummiboll..."}),
1984
2291
    ?line {Receiver2,Mref2} = spawn_monitor(fun()-> give_away_receiver(T2,Parent) end),
2000
2307
    ?line give_me = receive_any(),
2001
2308
    ?line {'EXIT',{badarg,_}} = (catch ets:give_away(T2,ReceiverNeg,"A deleted table")),
2002
2309
 
2003
 
    ?line T3 = ets:new(foo,[public | Opts]),
 
2310
    ?line T3 = ets_new(foo,[public | Opts]),
2004
2311
    spawn_link(fun()-> {'EXIT',{badarg,_}} = (catch ets:give_away(T3,ReceiverNeg,"From non owner")),
2005
2312
                       Parent ! done
2006
2313
               end),
2035
2342
 
2036
2343
setopts_do(Opts) ->
2037
2344
    Self = self(),
2038
 
    ?line T = ets:new(foo,[named_table, private | Opts]),
 
2345
    ?line T = ets_new(foo,[named_table, private | Opts]),
2039
2346
    ?line none = ets:info(T,heir),
2040
2347
    Heir = spawn_link(fun()->heir_heir(Self) end),
2041
2348
    ?line ets:setopts(T,{heir,Heir,"Data"}),
2088
2395
 
2089
2396
bad_table_do(Opts, DummyFile) ->
2090
2397
    Parent = self(),    
2091
 
    {Pid,Mref} = spawn_opt(fun()-> ets:new(priv,[private,named_table | Opts]),
2092
 
                                   Priv = ets:new(priv,[private | Opts]),
2093
 
                                   ets:new(prot,[protected,named_table | Opts]),
2094
 
                                   Prot = ets:new(prot,[protected | Opts]),
 
2398
    {Pid,Mref} = spawn_opt(fun()-> ets_new(priv,[private,named_table | Opts]),
 
2399
                                   Priv = ets_new(priv,[private | Opts]),
 
2400
                                   ets_new(prot,[protected,named_table | Opts]),
 
2401
                                   Prot = ets_new(prot,[protected | Opts]),
2095
2402
                                   Parent ! {self(),Priv,Prot},
2096
2403
                                   die_please = receive_any()
2097
2404
                           end,
2149
2456
 
2150
2457
bad_table_op({Opts,Priv,Prot}, Op) ->
2151
2458
    %%io:format("Doing Op=~p on ~p's\n",[Op,Type]),
2152
 
    T1 = ets:new(noname,Opts),
 
2459
    T1 = ets_new(noname,Opts),
2153
2460
    bad_table_call(noname,Op),
2154
2461
    ets:delete(T1),
2155
2462
    bad_table_call(T1,Op),
2156
 
    T2 = ets:new(named,[named_table | Opts]),
 
2463
    T2 = ets_new(named,[named_table | Opts]),
2157
2464
    ets:delete(T2),
2158
2465
    bad_table_call(named,Op),
2159
2466
    bad_table_call(T2,Op),
2187
2494
 
2188
2495
rename_do(Opts) ->
2189
2496
    ?line EtsMem = etsmem(),
2190
 
    ets:new(foobazz,[named_table, public | Opts]),
 
2497
    ets_new(foobazz,[named_table, public | Opts]),
2191
2498
    ets:insert(foobazz,{foo,bazz}),
2192
2499
    ungermanbazz = ets:rename(foobazz,ungermanbazz),
2193
2500
    {'EXIT',{badarg, _}} = (catch ets:lookup(foobazz,foo)),
2205
2512
 
2206
2513
rename_unnamed_do(Opts) ->
2207
2514
    ?line EtsMem = etsmem(),
2208
 
    ?line Tab = ets:new(bonkz,[public | Opts]),
 
2515
    ?line Tab = ets_new(bonkz,[public | Opts]),
2209
2516
    ?line {'EXIT',{badarg, _}} = (catch ets:insert(bonkz,{foo,bazz})),
2210
2517
    ?line bonkz = ets:info(Tab, name),
2211
2518
    ?line Tab = ets:rename(Tab, tjabonkz),
2224
2531
 
2225
2532
evil_rename_1(Old, New, Flags) ->
2226
2533
    ?line process_flag(trap_exit, true),
2227
 
    ?line Old = ets:new(Old, Flags),
 
2534
    ?line Old = ets_new(Old, Flags),
2228
2535
    ?line Fixer = fun() -> ets:safe_fixtable(Old, true) end,
2229
2536
    ?line crazy_fixtable(15000, Fixer),
2230
2537
    ?line erlang:yield(),
2234
2541
    ok.
2235
2542
 
2236
2543
crazy_fixtable(N, Fixer) ->
2237
 
    Dracula = ets:new(count_dracula, [public]),
 
2544
    Dracula = ets_new(count_dracula, [public]),
2238
2545
    ets:insert(Dracula, {count,0}),
2239
2546
    SpawnFun = fun() ->
2240
2547
                       Fixer(),
2268
2575
    ets:delete(T1).
2269
2576
 
2270
2577
evil_create_fixed_tab() ->
2271
 
    T = ets:new(arne, [public]),
 
2578
    T = ets_new(arne, [public]),
2272
2579
    ets:safe_fixtable(T, true),
2273
2580
    T.
2274
2581
 
2282
2589
 
2283
2590
interface_equality_do(Opts) ->
2284
2591
    ?line EtsMem = etsmem(),
2285
 
    ?line Set = ets:new(set,[set | Opts]),
2286
 
    ?line OrderedSet = ets:new(ordered_set,[ordered_set | Opts]),
 
2592
    ?line Set = ets_new(set,[set | Opts]),
 
2593
    ?line OrderedSet = ets_new(ordered_set,[ordered_set | Opts]),
2287
2594
    ?line F = fun(X,T,FF) -> case X of 
2288
2595
                           0 -> true; 
2289
2596
                           _ -> 
2362
2669
                             FF(X-1,T,FF) 
2363
2670
                     end 
2364
2671
        end,
2365
 
    ?line T1 = ets:new(xxx,[ordered_set| Opts]),
 
2672
    ?line T1 = ets_new(xxx,[ordered_set| Opts]),
2366
2673
    ?line F(3000,T1,F),
2367
2674
    ?line [[3,3],[3,3],[3,3]] = ets:match(T1, {'_','_','$1','$2',3}),
2368
2675
    ?line F2 = fun(X,Rem,Res,FF) -> case X of 
2400
2707
 
2401
2708
ordered_do(Opts) ->
2402
2709
    ?line EtsMem = etsmem(),
2403
 
    ?line T = ets:new(oset, [ordered_set | Opts]),
 
2710
    ?line T = ets_new(oset, [ordered_set | Opts]),
2404
2711
    ?line InsList = [ 
2405
2712
                      25,26,27,28,
2406
2713
                      5,6,7,8,
2461
2768
setbag(suite) -> [];
2462
2769
setbag(Config) when is_list(Config) ->    
2463
2770
    ?line EtsMem = etsmem(),
2464
 
    ?line Set = ets:new(set,[set]),
2465
 
    ?line Bag = ets:new(bag,[bag]),
 
2771
    ?line Set = ets_new(set,[set]),
 
2772
    ?line Bag = ets_new(bag,[bag]),
2466
2773
    ?line Key = {foo,bar},
2467
2774
    
2468
2775
    %% insert some value
2482
2789
    ?line verify_etsmem(EtsMem).
2483
2790
 
2484
2791
badnew(doc) ->
2485
 
    ["Test case to check proper return values for illegal ets:new() calls."];
 
2792
    ["Test case to check proper return values for illegal ets_new() calls."];
2486
2793
badnew(suite) -> [];
2487
2794
badnew(Config) when is_list(Config) ->
2488
2795
    ?line EtsMem = etsmem(),
2489
 
    ?line {'EXIT',{badarg,_}} = (catch ets:new(12,[])),
2490
 
    ?line {'EXIT',{badarg,_}} = (catch ets:new({a,b},[])),
2491
 
    ?line {'EXIT',{badarg,_}} = (catch ets:new(name,[foo])),
2492
 
    ?line {'EXIT',{badarg,_}} = (catch ets:new(name,{bag})),
2493
 
    ?line {'EXIT',{badarg,_}} = (catch ets:new(name,bag)),
 
2796
    ?line {'EXIT',{badarg,_}} = (catch ets_new(12,[])),
 
2797
    ?line {'EXIT',{badarg,_}} = (catch ets_new({a,b},[])),
 
2798
    ?line {'EXIT',{badarg,_}} = (catch ets_new(name,[foo])),
 
2799
    ?line {'EXIT',{badarg,_}} = (catch ets_new(name,{bag})),
 
2800
    ?line {'EXIT',{badarg,_}} = (catch ets_new(name,bag)),
2494
2801
    ?line verify_etsmem(EtsMem).
2495
2802
 
2496
2803
verybadnew(doc) ->
2499
2806
verybadnew(suite) -> [];
2500
2807
verybadnew(Config) when is_list(Config) ->
2501
2808
    ?line EtsMem = etsmem(),
2502
 
    ?line {'EXIT',{badarg,_}} = (catch ets:new(verybad,[set|protected])),
 
2809
    ?line {'EXIT',{badarg,_}} = (catch ets_new(verybad,[set|protected])),
2503
2810
    ?line verify_etsmem(EtsMem).
2504
2811
 
2505
2812
named(doc) ->   ["Small check to see if named tables work."];
2576
2883
    ?line [] = ets:lookup(Prot,foo).
2577
2884
 
2578
2885
privacy_owner(Boss, Opts) ->
2579
 
    ets:new(pub, [public,named_table | Opts]),
2580
 
    ets:new(prot,[protected,named_table | Opts]),
2581
 
    ets:new(priv,[private,named_table | Opts]),
 
2886
    ets_new(pub, [public,named_table | Opts]),
 
2887
    ets_new(prot,[protected,named_table | Opts]),
 
2888
    ets_new(priv,[private,named_table | Opts]),
2582
2889
    Boss ! ok,
2583
2890
    privacy_owner_loop(Boss).
2584
2891
 
2605
2912
 
2606
2913
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2607
2914
 
2608
 
insert(doc) ->   ["Test proper and improper inserts into a table."];
2609
 
insert(suite) -> [empty,badinsert].
2610
2915
 
2611
2916
empty(doc) ->
2612
2917
    ["Check lookup in an empty table and lookup of a non-existing key"];
2616
2921
 
2617
2922
empty_do(Opts) ->
2618
2923
    ?line EtsMem = etsmem(),
2619
 
    ?line Tab = ets:new(foo,Opts),
 
2924
    ?line Tab = ets_new(foo,Opts),
2620
2925
    ?line [] = ets:lookup(Tab,key),
2621
2926
    ?line true = ets:insert(Tab,{key2,val}),
2622
2927
    ?line [] = ets:lookup(Tab,key),
2633
2938
    ?line EtsMem = etsmem(),
2634
2939
    ?line {'EXIT',{badarg,_}} = (catch ets:insert(foo,{key,val})),
2635
2940
    
2636
 
    ?line Tab = ets:new(foo,Opts),
 
2941
    ?line Tab = ets_new(foo,Opts),
2637
2942
    ?line {'EXIT',{badarg,_}} = (catch ets:insert(Tab,{})),
2638
2943
 
2639
 
    ?line Tab3 = ets:new(foo,[{keypos,3}| Opts]),
 
2944
    ?line Tab3 = ets_new(foo,[{keypos,3}| Opts]),
2640
2945
    ?line {'EXIT',{badarg,_}} = (catch ets:insert(Tab3,{a,b})),
2641
2946
 
2642
2947
    ?line {'EXIT',{badarg,_}} = (catch ets:insert(Tab,[key,val2])),
2646
2951
 
2647
2952
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2648
2953
 
2649
 
lookup(doc) -> ["Some tests for lookups (timing, bad lookups, etc.)."];
2650
 
lookup(suite) -> [time_lookup,badlookup,lookup_order].
2651
2954
 
2652
2955
time_lookup(doc) ->   ["Lookup timing."];
2653
2956
time_lookup(suite) -> [];
2660
2963
                                   "~p ets lookups/s",[Values]))}.
2661
2964
 
2662
2965
time_lookup_do(Opts) ->
2663
 
    ?line Tab = ets:new(foo,Opts),
 
2966
    ?line Tab = ets_new(foo,Opts),
2664
2967
    ?line fill_tab(Tab,foo),
2665
2968
    ?line ets:insert(Tab,{{a,key},foo}),
2666
2969
    ?line {Time,_} = ?t:timecall(test_server,do_times,
2675
2978
badlookup(Config) when is_list(Config) ->
2676
2979
    ?line EtsMem = etsmem(),
2677
2980
    ?line {'EXIT',{badarg,_}} = (catch ets:lookup(foo,key)),
2678
 
    ?line Tab = ets:new(foo,[]),
 
2981
    ?line Tab = ets_new(foo,[]),
2679
2982
    ?line ets:delete(Tab),
2680
2983
    ?line {'EXIT',{badarg,_}} = (catch ets:lookup(Tab,key)),
2681
2984
    ?line verify_etsmem(EtsMem).
2700
3003
    Pair = [{A,B},{B,A},{A,C},{C,A},{B,C},{C,B}],
2701
3004
    Combos = [{D1,D2,D3} || D1<-ABC, D2<-Pair, D3<-Pair],
2702
3005
    lists:foreach(fun({D1,{D2a,D2b},{D3a,D3b}}) ->
2703
 
                          T = ets:new(foo,Opts),
 
3006
                          T = ets_new(foo,Opts),
2704
3007
                          case Fixed of
2705
3008
                              true -> ets:safe_fixtable(T,true);
2706
3009
                              false -> ok
2774
3077
 
2775
3078
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2776
3079
 
2777
 
lookup_element(doc) -> ["Some tests for lookup_element."];
2778
 
lookup_element(suite) -> [lookup_element_mult].
2779
3080
 
2780
3081
lookup_element_mult(doc) ->   ["Multiple return elements (OTP-2386)"];
2781
3082
lookup_element_mult(suite) -> [];
2784
3085
 
2785
3086
lookup_element_mult_do(Opts) ->
2786
3087
    ?line EtsMem = etsmem(),
2787
 
    ?line T = ets:new(service, [bag, {keypos, 2} | Opts]),
 
3088
    ?line T = ets_new(service, [bag, {keypos, 2} | Opts]),
2788
3089
    ?line D = lists:reverse(lem_data()),
2789
3090
    ?line lists:foreach(fun(X) -> ets:insert(T, X) end, D),
2790
3091
    ?line ok = lem_crash_3(T),
 
3092
    ?line ets:insert(T, {0, "heap_key"}),
 
3093
    ?line ets:lookup_element(T, "heap_key", 2),
2791
3094
    ?line true = ets:delete(T),
2792
3095
    ?line verify_etsmem(EtsMem).
2793
3096
 
2815
3118
 
2816
3119
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2817
3120
 
2818
 
delete(doc) ->
2819
 
    ["Check delete functionality (proper/improper deletes)"];
2820
 
delete(suite) ->
2821
 
    [delete_elem,delete_tab,delete_large_tab,delete_large_named_table,evil_delete,
2822
 
     table_leak,baddelete,match_delete,match_delete3].
2823
3121
 
2824
3122
delete_elem(doc) ->
2825
3123
    ["Check delete of an element inserted in a `filled' table."];
2829
3127
 
2830
3128
delete_elem_do(Opts) ->
2831
3129
    ?line EtsMem = etsmem(),
2832
 
    ?line Tab = ets:new(foo,Opts),
 
3130
    ?line Tab = ets_new(foo,Opts),
2833
3131
    ?line fill_tab(Tab,foo),
2834
3132
    ?line ets:insert(Tab,{{b,key},foo}),
2835
3133
    ?line ets:insert(Tab,{{c,key},foo}),
2849
3147
delete_tab_do(Opts) ->
2850
3148
    Name = foo,
2851
3149
    ?line EtsMem = etsmem(),
2852
 
    ?line Name = ets:new(Name, [named_table | Opts]),
 
3150
    ?line Name = ets_new(Name, [named_table | Opts]),
2853
3151
    ?line true = ets:delete(foo),
2854
3152
    %% The name should be available again.
2855
 
    ?line Name = ets:new(Name, [named_table | Opts]),
 
3153
    ?line Name = ets_new(Name, [named_table | Opts]),
2856
3154
    ?line true = ets:delete(Name),
2857
3155
    ?line verify_etsmem(EtsMem).
2858
3156
 
2859
3157
delete_large_tab(doc) ->
2860
3158
    "Check that ets:delete/1 works and that other processes can run.";
2861
3159
delete_large_tab(Config) when is_list(Config) ->
2862
 
    ?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)],
 
3160
    ?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 200000)],
2863
3161
    ?line EtsMem = etsmem(),
2864
3162
    repeat_for_opts(fun(Opts) -> delete_large_tab_do(Opts,Data) end),
2865
3163
    ?line verify_etsmem(EtsMem).
2871
3169
 
2872
3170
 
2873
3171
delete_large_tab_1(Name, Flags, Data, Fix) ->
2874
 
    ?line Tab = ets:new(Name, Flags),
 
3172
    ?line Tab = ets_new(Name, Flags),
2875
3173
    ?line ets:insert(Tab, Data),
2876
3174
 
2877
3175
    case Fix of
2938
3236
    ?line delete_large_named_table_1(foo_hash, [named_table | Opts], Data, true).
2939
3237
 
2940
3238
delete_large_named_table_1(Name, Flags, Data, Fix) ->
2941
 
    ?line Tab = ets:new(Name, Flags),
 
3239
    ?line Tab = ets_new(Name, Flags),
2942
3240
    ?line ets:insert(Tab, Data),
2943
3241
 
2944
3242
    case Fix of
2951
3249
    Pid = spawn_link(fun() ->
2952
3250
                             receive
2953
3251
                                 {trace,Parent,call,_} ->
2954
 
                                     ets:new(Name, [named_table])
 
3252
                                     ets_new(Name, [named_table])
2955
3253
                             end
2956
3254
                     end),
2957
3255
    ?line erlang:trace(self(), true, [call,{tracer,Pid}]),
2985
3283
 
2986
3284
evil_delete_not_owner(Name, Flags, Data, Fix) ->
2987
3285
    io:format("Not owner: ~p, fix = ~p", [Name,Fix]),
2988
 
    ?line Tab = ets:new(Name, [public|Flags]),
 
3286
    ?line Tab = ets_new(Name, [public|Flags]),
2989
3287
    ?line ets:insert(Tab, Data),
2990
3288
    case Fix of
2991
3289
        false -> ok;
3010
3308
 
3011
3309
evil_delete_owner(Name, Flags, Data, Fix) ->
3012
3310
    ?line Fun = fun() ->
3013
 
                        ?line Tab = ets:new(Name, [public|Flags]),
 
3311
                        ?line Tab = ets_new(Name, [public|Flags]),
3014
3312
                        ?line ets:insert(Tab, Data),
3015
3313
                        case Fix of
3016
3314
                            false -> ok;
3037
3335
exit_large_table_owner(suite) ->
3038
3336
    [];
3039
3337
exit_large_table_owner(Config) when is_list(Config) ->
3040
 
    ?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)],
 
3338
    %%?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)],
 
3339
    ?line FEData = fun(Do) -> repeat_while(fun(500000) -> {false,ok};
 
3340
                                              (I) -> Do({erlang:phash2(I, 16#ffffff),I}),
 
3341
                                                     {true, I+1}
 
3342
                                           end, 1)
 
3343
                   end,
3041
3344
    ?line EtsMem = etsmem(),
3042
 
    repeat_for_opts(fun(Opts) -> exit_large_table_owner_do(Opts,Data,Config) end),
 
3345
    repeat_for_opts({exit_large_table_owner_do,{FEData,Config}}),
3043
3346
    ?line verify_etsmem(EtsMem).
3044
3347
 
3045
 
exit_large_table_owner_do(Opts,Data,Config) ->
3046
 
    ?line verify_rescheduling_exit(Config, Data, [named_table | Opts], true, 1, 1),
3047
 
    ?line verify_rescheduling_exit(Config, Data, Opts, false, 1, 1).
 
3348
exit_large_table_owner_do(Opts,{FEData,Config}) ->
 
3349
    ?line verify_rescheduling_exit(Config, FEData, [named_table | Opts], true, 1, 1),
 
3350
    ?line verify_rescheduling_exit(Config, FEData, Opts, false, 1, 1).
3048
3351
 
3049
3352
exit_many_large_table_owner(doc) -> [];
3050
3353
exit_many_large_table_owner(suite) -> [];
3051
3354
exit_many_large_table_owner(Config) when is_list(Config) ->
3052
 
    ?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)],
 
3355
    %%?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)],
 
3356
    ?line FEData = fun(Do) -> repeat_while(fun(500000) -> {false,ok};
 
3357
                                              (I) -> Do({erlang:phash2(I, 16#ffffff),I}),
 
3358
                                                     {true, I+1}
 
3359
                                           end, 1)
 
3360
                   end,
3053
3361
    ?line EtsMem = etsmem(),
3054
 
    repeat_for_opts(fun(Opts) -> exit_many_large_table_owner_do(Opts,Data,Config) end),
 
3362
    repeat_for_opts(fun(Opts) -> exit_many_large_table_owner_do(Opts,FEData,Config) end),
3055
3363
    ?line verify_etsmem(EtsMem).
3056
3364
 
3057
 
exit_many_large_table_owner_do(Opts,Data,Config) -> 
3058
 
    ?line verify_rescheduling_exit(Config, Data, Opts, true, 1, 4),
3059
 
    ?line verify_rescheduling_exit(Config, Data, [named_table | Opts], false, 1, 4).
 
3365
exit_many_large_table_owner_do(Opts,FEData,Config) ->
 
3366
    ?line verify_rescheduling_exit(Config, FEData, Opts, true, 1, 4),
 
3367
    ?line verify_rescheduling_exit(Config, FEData, [named_table | Opts], false, 1, 4).
3060
3368
 
3061
3369
exit_many_tables_owner(doc) -> [];
3062
3370
exit_many_tables_owner(suite) -> [];
3063
3371
exit_many_tables_owner(Config) when is_list(Config) ->
 
3372
    NoData = fun(_Do) -> ok end,
3064
3373
    ?line EtsMem = etsmem(),
3065
 
    ?line verify_rescheduling_exit(Config, [], [named_table], false, 1000, 1),
3066
 
    ?line verify_rescheduling_exit(Config, [], [named_table,{write_concurrency,true}], false, 1000, 1),
 
3374
    ?line verify_rescheduling_exit(Config, NoData, [named_table], false, 1000, 1),
 
3375
    ?line verify_rescheduling_exit(Config, NoData, [named_table,{write_concurrency,true}], false, 1000, 1),
3067
3376
    ?line verify_etsmem(EtsMem).
3068
3377
 
3069
3378
exit_many_many_tables_owner(doc) -> [];
3070
3379
exit_many_many_tables_owner(suite) -> [];
3071
3380
exit_many_many_tables_owner(Config) when is_list(Config) ->
3072
3381
    ?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 50)],
3073
 
    repeat_for_opts(fun(Opts) -> exit_many_many_tables_owner_do(Opts,Data,Config) end).
 
3382
    ?line FEData = fun(Do) -> lists:foreach(Do, Data) end,
 
3383
    repeat_for_opts(fun(Opts) -> exit_many_many_tables_owner_do(Opts,FEData,Config) end).
3074
3384
 
3075
 
exit_many_many_tables_owner_do(Opts,Data,Config) ->
3076
 
    ?line verify_rescheduling_exit(Config, Data, [named_table | Opts], true, 200, 5),
3077
 
    ?line verify_rescheduling_exit(Config, Data, Opts, false, 200, 5),
 
3385
exit_many_many_tables_owner_do(Opts,FEData,Config) ->
 
3386
    ?line verify_rescheduling_exit(Config, FEData, [named_table | Opts], true, 200, 5),
 
3387
    ?line verify_rescheduling_exit(Config, FEData, Opts, false, 200, 5),
3078
3388
    ?line wait_for_test_procs(),
3079
3389
    ?line EtsMem = etsmem(),
3080
 
    ?line verify_rescheduling_exit(Config, Data, Opts, true, 200, 5),
3081
 
    ?line verify_rescheduling_exit(Config, Data, [named_table | Opts], false, 200, 5),
 
3390
    ?line verify_rescheduling_exit(Config, FEData, Opts, true, 200, 5),
 
3391
    ?line verify_rescheduling_exit(Config, FEData, [named_table | Opts], false, 200, 5),
3082
3392
    ?line verify_etsmem(EtsMem).
3083
3393
    
3084
3394
 
3121
3431
    receive Go -> ok end,
3122
3432
    ok.
3123
3433
 
3124
 
verify_rescheduling_exit(Config, Data, Flags, Fix, NOTabs, NOProcs) ->
 
3434
verify_rescheduling_exit(Config, ForEachData, Flags, Fix, NOTabs, NOProcs) ->
3125
3435
    ?line NoFix = 5,
3126
3436
    ?line TestCase = atom_to_list(?config(test_case, Config)),
3127
3437
    ?line Parent = self(),
3136
3446
                                         ++ "-" ++ integer_to_list(A)
3137
3447
                                         ++ "-" ++ integer_to_list(B)
3138
3448
                                         ++ "-" ++ integer_to_list(C)),
3139
 
                          Tab = ets:new(Name, Flags),
3140
 
                          ets:insert(Tab, Data),
 
3449
                          Tab = ets_new(Name, Flags),
 
3450
                          ForEachData(fun(Data) -> ets:insert(Tab, Data) end),
3141
3451
                          case Fix of
3142
3452
                              false -> ok;
3143
3453
                              true ->
3145
3455
                                                        vre_fix_tables(Tab)
3146
3456
                                                end,
3147
3457
                                                lists:seq(1,NoFix)),
3148
 
                                  lists:foreach(fun({K,_}) ->
3149
 
                                                        ets:delete(Tab, K)
3150
 
                                                end,
3151
 
                                                Data)
 
3458
                                  KeyPos = ets:info(Tab,keypos),
 
3459
                                  ForEachData(fun(Data) ->
 
3460
                                                ets:delete(Tab, element(KeyPos,Data))
 
3461
                                              end)
3152
3462
                          end
3153
3463
                  end,
3154
3464
                  NOTabs),
3195
3505
 
3196
3506
table_leak_1(_,0) -> ok;
3197
3507
table_leak_1(Opts,N) ->
3198
 
    ?line T = ets:new(fooflarf, Opts),
 
3508
    ?line T = ets_new(fooflarf, Opts),
3199
3509
    ?line true = ets:delete(T),
3200
3510
    table_leak_1(Opts,N-1).
3201
3511
 
3205
3515
baddelete(Config) when is_list(Config) ->
3206
3516
    ?line EtsMem = etsmem(),
3207
3517
    ?line {'EXIT',{badarg,_}} = (catch ets:delete(foo)),
3208
 
    ?line Tab = ets:new(foo,[]),
 
3518
    ?line Tab = ets_new(foo,[]),
3209
3519
    ?line true = ets:delete(Tab),
3210
3520
    ?line {'EXIT',{badarg,_}} = (catch ets:delete(Tab)),
3211
3521
    ?line verify_etsmem(EtsMem).
3220
3530
 
3221
3531
match_delete_do(Opts) ->
3222
3532
    ?line EtsMem = etsmem(),
3223
 
    ?line Tab = ets:new(kad,Opts),
 
3533
    ?line Tab = ets_new(kad,Opts),
3224
3534
    ?line fill_tab(Tab,foo),
3225
3535
    ?line ets:insert(Tab,{{c,key},bar}),
3226
3536
    ?line _ = ets:match_delete(Tab,{'_',foo}),
3264
3574
 
3265
3575
firstnext_do(Opts) ->
3266
3576
    ?line EtsMem = etsmem(),
3267
 
    ?line Tab = ets:new(foo,Opts),
 
3577
    ?line Tab = ets_new(foo,Opts),
3268
3578
    ?line [] = firstnext_collect(Tab,ets:first(Tab),[]),
3269
3579
    ?line fill_tab(Tab,foo),
3270
3580
    ?line Len = length(ets:tab2list(Tab)),
3287
3597
    [dynamic_go() || _ <- lists:seq(1, 2)],
3288
3598
    receive
3289
3599
        after 5000 -> ok
3290
 
        end.
 
3600
    end.
3291
3601
 
3292
3602
ets_init(Tab, N) ->
3293
 
    ets:new(Tab, [named_table,public,ordered_set]),
 
3603
    ets_new(Tab, [named_table,public,ordered_set]),
3294
3604
    cycle(Tab, lists:seq(1,N+1)).
3295
3605
 
3296
3606
cycle(_Tab, [H|T]) when H > length(T)-> ok;
3323
3633
 
3324
3634
slot_do(Opts) ->
3325
3635
    ?line EtsMem = etsmem(),
3326
 
    ?line Tab = ets:new(foo,Opts),
 
3636
    ?line Tab = ets_new(foo,Opts),
3327
3637
    ?line fill_tab(Tab,foo),
3328
3638
    ?line Elts = ets:info(Tab,size),
3329
3639
    ?line Elts = slot_loop(Tab,0,0),
3342
3652
 
3343
3653
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
3344
3654
 
3345
 
match(suite) -> [match1, match2, match_object, match_object2].
3346
3655
 
3347
3656
match1(suite) -> [];
3348
3657
match1(Config) when is_list(Config) ->
3350
3659
 
3351
3660
match1_do(Opts) ->
3352
3661
    ?line EtsMem = etsmem(),
3353
 
    ?line Tab = ets:new(foo,Opts),
 
3662
    ?line Tab = ets_new(foo,Opts),
3354
3663
    ?line fill_tab(Tab,foo),
3355
3664
    ?line [] = ets:match(Tab,{}),
3356
3665
    ?line ets:insert(Tab,{{one,4},4}),
3415
3724
 
3416
3725
match_object_do(Opts) ->
3417
3726
    ?line EtsMem = etsmem(),
3418
 
    ?line Tab = ets:new(foobar, Opts),
 
3727
    ?line Tab = ets_new(foobar, Opts),
3419
3728
    ?line fill_tab(Tab, foo),
3420
3729
    ?line ets:insert(Tab, {{one, 4}, 4}),
3421
3730
    ?line ets:insert(Tab,{{one,5},5}),
3459
3768
 
3460
3769
match_object2_do(Opts) ->
3461
3770
    ?line EtsMem = etsmem(),
3462
 
    ?line Tab = ets:new(foo, [bag, {keypos, 2} | Opts]),
 
3771
    ?line Tab = ets_new(foo, [bag, {keypos, 2} | Opts]),
3463
3772
    ?line fill_tab2(Tab, 0, 13005),     % match_db_object does 1000
3464
3773
                                       % elements per pass, might
3465
3774
                                       % change in the future.
3477
3786
 
3478
3787
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
3479
3788
 
3480
 
misc(suite) -> [misc1, safe_fixtable, info, dups, tab2list].
3481
3789
 
3482
3790
tab2list(doc) -> ["Tests tab2list (OTP-3319)"];
3483
3791
tab2list(suite) -> [];
3498
3806
 
3499
3807
misc1_do(Opts) ->
3500
3808
    ?line EtsMem = etsmem(),
3501
 
    ?line Tab = ets:new(foo,Opts),
 
3809
    ?line Tab = ets_new(foo,Opts),
3502
3810
    ?line true = lists:member(Tab,ets:all()),
3503
3811
    ?line ets:delete(Tab),
3504
3812
    ?line false = lists:member(Tab,ets:all()),
3517
3825
 
3518
3826
safe_fixtable_do(Opts) ->
3519
3827
    ?line EtsMem = etsmem(),
3520
 
    ?line Tab = ets:new(foo, Opts),
 
3828
    ?line Tab = ets_new(foo, Opts),
3521
3829
    ?line fill_tab(Tab, foobar),
3522
3830
    ?line true = ets:safe_fixtable(Tab, true),
3523
3831
    ?line receive after 1 -> ok end,
3556
3864
    ?line EtsMem = etsmem(),
3557
3865
    ?line MeMyselfI=self(),
3558
3866
    ?line ThisNode=node(),
3559
 
    ?line Tab = ets:new(foobar, [{keypos, 2} | Opts]),
 
3867
    ?line Tab = ets_new(foobar, [{keypos, 2} | Opts]),
3560
3868
 
3561
3869
    %% Note: ets:info/1 used to return a tuple, but from R11B onwards it
3562
3870
    %% returns a list.
3610
3918
 
3611
3919
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
3612
3920
 
3613
 
files(suite) -> [tab2file, tab2file2, tab2file3, tabfile_ext1, tabfile_ext2,
3614
 
                 tabfile_ext3, tabfile_ext4].
3615
 
 
3616
3921
tab2file(doc) -> ["Check the ets:tab2file function on an empty "
3617
3922
                  "ets table."];
3618
3923
tab2file(suite) -> [];
3619
3924
tab2file(Config) when is_list(Config) ->
3620
3925
    %% Write an empty ets table to a file, read back and check properties.
3621
 
    ?line Tab = ets:new(ets_SUITE_foo_tab, [named_table, set, private,
 
3926
    ?line Tab = ets_new(ets_SUITE_foo_tab, [named_table, set, private,
3622
3927
                                            {keypos, 2}]),
3623
3928
    ?line FName = filename:join([?config(priv_dir, Config),"tab2file_case"]),
3624
3929
    ?line ok = ets:tab2file(Tab, FName),
3634
3939
    ?line verify_etsmem(EtsMem).
3635
3940
    
3636
3941
tab2file2(doc) -> ["Check the ets:tab2file function on a ",
3637
 
                   "filled set type ets table."];
 
3942
                   "filled set/bag type ets table."];
3638
3943
tab2file2(suite) -> [];
3639
 
tab2file2(Config) when is_list(Config) ->       
3640
 
    %% Try the same on a filled set table.
 
3944
tab2file2(Config) when is_list(Config) ->
 
3945
    repeat_for_opts({tab2file2_do,Config}, [[set,bag],compressed]).
 
3946
 
 
3947
tab2file2_do(Opts, Config) ->
3641
3948
    ?line EtsMem = etsmem(),
3642
 
    ?line Tab = ets:new(ets_SUITE_foo_tab, [named_table, set, private,
3643
 
                                            {keypos, 2}]),
 
3949
    ?line Tab = ets_new(ets_SUITE_foo_tab, [named_table, private,
 
3950
                                            {keypos, 2} | Opts]),
3644
3951
    ?line FName = filename:join([?config(priv_dir, Config),"tab2file2_case"]),
3645
3952
    ?line ok = fill_tab2(Tab, 0, 10000),   % Fill up the table (grucho mucho!)
3646
3953
    ?line Len = length(ets:tab2list(Tab)),
3647
 
    ?line ok = ets:tab2file(Tab, FName),
3648
 
    ?line true = ets:delete(Tab),
3649
 
    %
3650
 
    ?line {ok, Tab2} = ets:file2tab(FName),
3651
 
    ?line private = ets:info(Tab2, protection),
3652
 
    ?line true = ets:info(Tab2, named_table),
3653
 
    ?line 2 = ets:info(Tab2, keypos),
3654
 
    ?line set = ets:info(Tab2, type),
3655
 
    ?line Len = length(ets:tab2list(Tab2)),
3656
 
    ?line true = ets:delete(Tab2),
3657
 
    ?line verify_etsmem(EtsMem).
3658
 
 
3659
 
tab2file3(doc) -> ["Check the ets:tab2file function on a ",
3660
 
                   "filled bag type ets table."];
3661
 
tab2file3(suite) -> [];
3662
 
tab2file3(Config) when is_list(Config) ->
3663
 
    %% Try the same on a filled bag table.
3664
 
    ?line EtsMem = etsmem(),
3665
 
    ?line Tab = ets:new(ets_SUITE_foo_tab, [named_table, bag, private,
3666
 
                                            {keypos, 2}]),
3667
 
    ?line FName = filename:join([?config(priv_dir, Config),"tab2file3_case"]),
3668
 
    ?line ok = fill_tab2(Tab, 0, 10000),   % Fill up the table (grucho mucho!)
3669
 
    ?line Len = length(ets:tab2list(Tab)),
3670
3954
    ?line Mem = ets:info(Tab, memory),
 
3955
    ?line Type = ets:info(Tab, type),
 
3956
    %%io:format("org tab: ~p\n",[ets:info(Tab)]),
3671
3957
    ?line ok = ets:tab2file(Tab, FName),
3672
3958
    ?line true = ets:delete(Tab),
3673
3959
 
 
3960
    ?line EtsMem4 = etsmem(),
 
3961
 
3674
3962
    ?line {ok, Tab2} = ets:file2tab(FName),
 
3963
    %%io:format("loaded tab: ~p\n",[ets:info(Tab2)]),
3675
3964
    ?line private = ets:info(Tab2, protection),
3676
3965
    ?line true = ets:info(Tab2, named_table),
3677
3966
    ?line 2 = ets:info(Tab2, keypos),
3678
 
    ?line bag = ets:info(Tab2, type),
 
3967
    ?line Type = ets:info(Tab2, type),
3679
3968
    ?line Len = length(ets:tab2list(Tab2)),
3680
3969
    ?line Mem = ets:info(Tab2, memory),
3681
3970
    ?line true = ets:delete(Tab2),
 
3971
    io:format("Between = ~p\n", [EtsMem4]),
3682
3972
    ?line verify_etsmem(EtsMem).
3683
3973
 
3684
3974
-define(test_list, [8,5,4,1,58,125,255, 250, 245, 240, 235,
3722
4012
    ?line FName = filename:join([?config(priv_dir, Config),"nisse.dat"]),
3723
4013
    ?line FName2 = filename:join([?config(priv_dir, Config),"countflip.dat"]),
3724
4014
    L = lists:seq(1,10),
3725
 
    T = ets:new(x,Opts),
 
4015
    T = ets_new(x,Opts),
3726
4016
    Name = make_ref(),
3727
4017
    [ets:insert(T,{X,integer_to_list(X)}) || X <- L],
3728
4018
    ok = ets:tab2file(T,FName,[{extended_info,[object_count]}]),
3762
4052
    ?line FName = filename:join([?config(priv_dir, Config),"olle.dat"]),
3763
4053
    ?line FName2 = filename:join([?config(priv_dir, Config),"bitflip.dat"]),
3764
4054
    L = lists:seq(1,10),
3765
 
    T = ets:new(x,Opts),
 
4055
    T = ets_new(x,Opts),
3766
4056
    Name = make_ref(),
3767
4057
    [ets:insert(T,{X,integer_to_list(X)}) || X <- L],
3768
4058
    ok = ets:tab2file(T,FName,[{extended_info,[md5sum]}]),
3800
4090
    ?line FName2 = filename:join([?config(priv_dir, Config),"ncountflip.dat"]),
3801
4091
    L = lists:seq(1,10),
3802
4092
    Name = make_ref(),
3803
 
    ?MODULE = ets:new(?MODULE,[named_table]),
 
4093
    ?MODULE = ets_new(?MODULE,[named_table]),
3804
4094
    [ets:insert(?MODULE,{X,integer_to_list(X)}) || X <- L],
3805
4095
    ets:tab2file(?MODULE,FName),
3806
4096
    {error,cannot_create_table} = ets:file2tab(FName),
3832
4122
tabfile_ext4(Config) when is_list(Config) ->
3833
4123
    ?line FName = filename:join([?config(priv_dir, Config),"bauta.dat"]),
3834
4124
    LL = lists:seq(1,10000),
3835
 
    TL = ets:new(x,[]),
 
4125
    TL = ets_new(x,[]),
3836
4126
    Name2 = make_ref(),
3837
4127
    [ets:insert(TL,{X,integer_to_list(X)}) || X <- LL],
3838
4128
    ok = ets:tab2file(TL,FName,[{extended_info,[md5sum]}]),
3877
4167
    {_,B} = split_binary(Bin, N+1),
3878
4168
    B.
3879
4169
 
3880
 
heavy(suite) -> [heavy_lookup, heavy_lookup_element].
3881
4170
 
3882
4171
%% Lookup stuff like crazy...
3883
4172
heavy_lookup(doc) -> ["Performs multiple lookups for every key ",
3888
4177
 
3889
4178
heavy_lookup_do(Opts) ->
3890
4179
    ?line EtsMem = etsmem(),
3891
 
    ?line Tab = ets:new(foobar_table, [set, protected, {keypos, 2} | Opts]),
 
4180
    ?line Tab = ets_new(foobar_table, [set, protected, {keypos, 2} | Opts]),
3892
4181
    ?line ok = fill_tab2(Tab, 0, 7000),
3893
4182
    ?line ?t:do_times(50, ?MODULE, do_lookup, [Tab, 6999]),
3894
4183
    ?line true = ets:delete(Tab),
3911
4200
 
3912
4201
heavy_lookup_element_do(Opts) ->
3913
4202
    ?line EtsMem = etsmem(),
3914
 
    ?line Tab = ets:new(foobar_table, [set, protected, {keypos, 2} | Opts]),
 
4203
    ?line Tab = ets_new(foobar_table, [set, protected, {keypos, 2} | Opts]),
3915
4204
    ?line ok = fill_tab2(Tab, 0, 7000),
3916
4205
    case os:type() of
3917
4206
        vxworks ->
3940
4229
    end.
3941
4230
 
3942
4231
 
3943
 
fold(suite) -> [foldl_ordered, foldr_ordered,
3944
 
                foldl, foldr,
3945
 
                fold_empty].
 
4232
heavy_concurrent(Config) when is_list(Config) ->
 
4233
    repeat_for_opts(do_heavy_concurrent).
 
4234
 
 
4235
do_heavy_concurrent(Opts) ->
 
4236
    ?line Size = 10000,
 
4237
    ?line EtsMem = etsmem(),
 
4238
    ?line Tab = ets_new(blupp, [set, public, {keypos, 2} | Opts]),
 
4239
    ?line ok = fill_tab2(Tab, 0, Size),
 
4240
    ?line Procs = lists:map(
 
4241
                    fun (N) ->
 
4242
                            spawn_link(
 
4243
                              fun () ->
 
4244
                                      do_heavy_concurrent_proc(Tab, Size, N)
 
4245
                              end)
 
4246
                    end,
 
4247
                    lists:seq(1, 500)),
 
4248
    ?line lists:foreach(fun (P) ->
 
4249
                                M = erlang:monitor(process, P),
 
4250
                                receive
 
4251
                                    {'DOWN', M, process, P, _} ->
 
4252
                                        ok
 
4253
                                end
 
4254
                        end,
 
4255
                        Procs),
 
4256
    ?line true = ets:delete(Tab),
 
4257
    ?line verify_etsmem(EtsMem).
 
4258
 
 
4259
do_heavy_concurrent_proc(_Tab, 0, _Offs) ->
 
4260
    done;
 
4261
do_heavy_concurrent_proc(Tab, N, Offs) when (N+Offs) rem 100 == 0 ->
 
4262
    Data = {"here", are, "S O M E ", data, "toooooooooooooooooo", insert,
 
4263
            make_ref(), make_ref(), make_ref()},
 
4264
    true=ets:insert(Tab, {{self(),Data}, N}),
 
4265
    do_heavy_concurrent_proc(Tab, N-1, Offs);
 
4266
do_heavy_concurrent_proc(Tab, N, Offs) ->
 
4267
    _ = ets:lookup(Tab, N),
 
4268
    do_heavy_concurrent_proc(Tab, N-1, Offs).
 
4269
 
3946
4270
 
3947
4271
fold_empty(doc) ->
3948
4272
    [];
4012
4336
 
4013
4337
member_do(Opts) ->
4014
4338
    ?line EtsMem = etsmem(),
4015
 
    ?line T = ets:new(xxx, Opts),
 
4339
    ?line T = ets_new(xxx, Opts),
4016
4340
    ?line false = ets:member(T,hej),
4017
4341
    ?line E = fun(0,_F)->ok;
4018
4342
                 (N,F) -> 
4037
4361
 
4038
4362
 
4039
4363
build_table(L1,L2,Num) ->
4040
 
    T = ets:new(xxx, [ordered_set]
 
4364
    T = ets_new(xxx, [ordered_set]
4041
4365
               ),
4042
4366
    lists:foreach(
4043
4367
      fun(X1) ->
4059
4383
    T.
4060
4384
 
4061
4385
build_table2(L1,L2,Num) ->
4062
 
    T = ets:new(xxx, [ordered_set]
 
4386
    T = ets_new(xxx, [ordered_set]
4063
4387
               ),
4064
4388
    lists:foreach(
4065
4389
      fun(X1) ->
4190
4514
    do_n_times(Fun,N-1).
4191
4515
 
4192
4516
make_table(Name, Options, Elements) ->
4193
 
    T = ets:new(Name, Options),
 
4517
    T = ets_new(Name, Options),
4194
4518
    lists:foreach(fun(E) -> ets:insert(T, E) end, Elements),
4195
4519
    T.
4196
4520
filltabint(Tab,0) ->
4254
4578
fill_sets_int(N) ->
4255
4579
    fill_sets_int(N,[]).
4256
4580
fill_sets_int(N,Opts) ->
4257
 
    Tab1 = ets:new(xxx, [ordered_set|Opts]),
 
4581
    Tab1 = ets_new(xxx, [ordered_set|Opts]),
4258
4582
    filltabint(Tab1,N),
4259
 
    Tab2 = ets:new(xxx, [set|Opts]),
 
4583
    Tab2 = ets_new(xxx, [set|Opts]),
4260
4584
    filltabint(Tab2,N),
4261
 
    Tab3 = ets:new(xxx, [bag|Opts]),
 
4585
    Tab3 = ets_new(xxx, [bag|Opts]),
4262
4586
    filltabint2(Tab3,N),
4263
 
    Tab4 = ets:new(xxx, [duplicate_bag|Opts]),
 
4587
    Tab4 = ets_new(xxx, [duplicate_bag|Opts]),
4264
4588
    filltabint3(Tab4,N),
4265
4589
    [Tab1,Tab2,Tab3,Tab4].
4266
4590
 
4412
4736
                  "testdets_" ++ integer_to_list(N) ++ ".dets").
4413
4737
 
4414
4738
otp_6842_select_1000(Config) when is_list(Config) -> 
4415
 
    ?line Tab = ets:new(xxx,[ordered_set]),
 
4739
    ?line Tab = ets_new(xxx,[ordered_set]),
4416
4740
    ?line [ets:insert(Tab,{X,X}) || X <- lists:seq(1,10000)],
4417
4741
    ?line AllTrue = lists:duplicate(10,true),
4418
4742
    ?line AllTrue = 
4445
4769
 
4446
4770
otp_6338(Config) when is_list(Config) ->
4447
4771
    L = binary_to_term(<<131,108,0,0,0,2,104,2,108,0,0,0,2,103,100,0,19,112,112,98,49,95,98,115,49,50,64,98,108,97,100,101,95,48,95,53,0,0,33,50,0,0,0,4,1,98,0,0,23,226,106,100,0,4,101,120,105,116,104,2,108,0,0,0,2,104,2,100,0,3,115,98,109,100,0,19,112,112,98,50,95,98,115,49,50,64,98,108,97,100,101,95,48,95,56,98,0,0,18,231,106,100,0,4,114,101,99,118,106>>),
4448
 
    T = ets:new(xxx,[ordered_set]),
 
4772
    T = ets_new(xxx,[ordered_set]),
4449
4773
    lists:foreach(fun(X) -> ets:insert(T,X) end,L),
4450
4774
    [[4839,recv]] = ets:match(T,{[{sbm,ppb2_bs12@blade_0_8},'$1'],'$2'}),
4451
4775
    ets:delete(T).
4456
4780
 
4457
4781
otp_5340_do(Opts) ->
4458
4782
    N = 3000,
4459
 
    T = ets:new(otp_5340, [bag,public | Opts]),
 
4783
    T = ets_new(otp_5340, [bag,public | Opts]),
4460
4784
    Ids = [1,2,3,4,5],
4461
4785
    [w(T, N, Id) || Id <- Ids],
4462
4786
    verify(T, Ids),
4492
4816
    repeat_for_opts(otp_7665_do).
4493
4817
 
4494
4818
otp_7665_do(Opts) ->
4495
 
    Tab = ets:new(otp_7665,[bag | Opts]),
 
4819
    Tab = ets_new(otp_7665,[bag | Opts]),
4496
4820
    Min = 0,
4497
4821
    Max = 10,
4498
4822
    lists:foreach(fun(N)-> otp_7665_act(Tab,Min,Max,N) end,
4530
4854
 
4531
4855
meta_wb_do(Opts) ->
4532
4856
    %% Do random new/delete/rename of colliding named tables
4533
 
    Names = [pioneer | colliding_names(pioneer)],
 
4857
    Names0 = [pioneer | colliding_names(pioneer)],
 
4858
 
 
4859
    %% Remove any names that happen to exist as tables already
 
4860
    Names = lists:filter(fun(Name) -> ets:info(Name) == undefined end,
 
4861
                         Names0),
4534
4862
    Len = length(Names),
4535
4863
    OpFuns = {fun meta_wb_new/4, fun meta_wb_delete/4, fun meta_wb_rename/4},
4536
4864
 
 
4865
    ?line true = (Len >= 3),
 
4866
 
4537
4867
    io:format("Colliding names = ~p\n",[Names]),
4538
4868
    F = fun(0,_,_) -> ok;
4539
4869
           (N,Tabs,Me) -> Name1 = lists:nth(random:uniform(Len),Names), 
4549
4879
                  Names).
4550
4880
    
4551
4881
meta_wb_new(Name, _, Tabs, Opts) ->
4552
 
    case (catch ets:new(Name,[named_table|Opts])) of
 
4882
    case (catch ets_new(Name,[named_table|Opts])) of
4553
4883
        Name ->
4554
4884
            ?line false = lists:member(Name, Tabs),
4555
4885
            [Name | Tabs];      
4597
4927
grow_shrink_0([], _) -> ok.
4598
4928
 
4599
4929
grow_shrink_1(N, Flags) ->
4600
 
    ?line T = ets:new(a, Flags),
 
4930
    ?line T = ets_new(a, Flags),
4601
4931
    ?line grow_shrink_2(N, N, T),
4602
4932
    ?line ets:delete(T).
4603
4933
 
4627
4957
grow_pseudo_deleted_do(Type) ->
4628
4958
    process_flag(scheduler,1),
4629
4959
    Self = self(),
4630
 
    ?line T = ets:new(kalle,[Type,public,{write_concurrency,true}]),
 
4960
    ?line T = ets_new(kalle,[Type,public,{write_concurrency,true}]),
4631
4961
    Mod = 7, Mult = 10000,
4632
4962
    filltabint(T,Mod*Mult),
4633
4963
    ?line true = ets:safe_fixtable(T,true),
4669
4999
shrink_pseudo_deleted_do(Type) ->
4670
5000
    process_flag(scheduler,1),
4671
5001
    Self = self(),
4672
 
    ?line T = ets:new(kalle,[Type,public,{write_concurrency,true}]),
 
5002
    ?line T = ets_new(kalle,[Type,public,{write_concurrency,true}]),
4673
5003
    Half = 10000,
4674
5004
    filltabint(T,Half*2),
4675
5005
    ?line true = ets:safe_fixtable(T,true),
4698
5028
    process_flag(scheduler,0).
4699
5029
 
4700
5030
    
4701
 
meta_smp(suite) ->
4702
 
    [meta_lookup_unnamed_read,
4703
 
     meta_lookup_unnamed_write,
4704
 
     meta_lookup_named_read,
4705
 
     meta_lookup_named_write,
4706
 
     meta_newdel_unnamed,
4707
 
     meta_newdel_named].
4708
5031
 
4709
5032
meta_lookup_unnamed_read(suite) -> [];
4710
5033
meta_lookup_unnamed_read(Config) when is_list(Config) ->
4711
 
    InitF = fun(_) -> Tab = ets:new(unnamed,[]),
 
5034
    InitF = fun(_) -> Tab = ets_new(unnamed,[]),
4712
5035
                     true = ets:insert(Tab,{key,data}),
4713
5036
                     Tab
4714
5037
            end,
4721
5044
 
4722
5045
meta_lookup_unnamed_write(suite) -> [];
4723
5046
meta_lookup_unnamed_write(Config) when is_list(Config) ->
4724
 
    InitF = fun(_) -> Tab = ets:new(unnamed,[]),
 
5047
    InitF = fun(_) -> Tab = ets_new(unnamed,[]),
4725
5048
                          {Tab,0}
4726
5049
            end,
4727
5050
    ExecF = fun({Tab,N}) -> true = ets:insert(Tab,{key,N}),
4734
5057
meta_lookup_named_read(suite) -> [];
4735
5058
meta_lookup_named_read(Config) when is_list(Config) ->
4736
5059
    InitF = fun([ProcN|_]) -> Name = list_to_atom(integer_to_list(ProcN)),
4737
 
                              Tab = ets:new(Name,[named_table]),
 
5060
                              Tab = ets_new(Name,[named_table]),
4738
5061
                              true = ets:insert(Tab,{key,data}),
4739
5062
                              Tab
4740
5063
            end,
4748
5071
meta_lookup_named_write(suite) -> [];
4749
5072
meta_lookup_named_write(Config) when is_list(Config) ->
4750
5073
    InitF = fun([ProcN|_]) -> Name = list_to_atom(integer_to_list(ProcN)),
4751
 
                          Tab = ets:new(Name,[named_table]),
 
5074
                          Tab = ets_new(Name,[named_table]),
4752
5075
                          {Tab,0}
4753
5076
            end,
4754
5077
    ExecF = fun({Tab,N}) -> true = ets:insert(Tab,{key,N}),
4761
5084
meta_newdel_unnamed(suite) -> [];
4762
5085
meta_newdel_unnamed(Config) when is_list(Config) ->
4763
5086
    InitF = fun(_) -> ok end,
4764
 
    ExecF = fun(_) -> Tab = ets:new(unnamed,[]),
 
5087
    ExecF = fun(_) -> Tab = ets_new(unnamed,[]),
4765
5088
                      true = ets:delete(Tab)
4766
5089
            end,
4767
5090
    FiniF = fun(_) -> ok end,
4771
5094
meta_newdel_named(Config) when is_list(Config) ->
4772
5095
    InitF = fun([ProcN|_]) -> list_to_atom(integer_to_list(ProcN))
4773
5096
            end,
4774
 
    ExecF = fun(Name) -> Name = ets:new(Name,[named_table]),
 
5097
    ExecF = fun(Name) -> Name = ets_new(Name,[named_table]),
4775
5098
                         true = ets:delete(Name),
4776
5099
                         Name
4777
5100
            end,
4781
5104
smp_insert(doc) -> ["Concurrent insert's on same table"];
4782
5105
smp_insert(suite) -> [];
4783
5106
smp_insert(Config) when is_list(Config) ->
4784
 
    ets:new(smp_insert,[named_table,public,{write_concurrency,true}]),
 
5107
    ets_new(smp_insert,[named_table,public,{write_concurrency,true}]),
4785
5108
    InitF = fun(_) -> ok end,
4786
5109
    ExecF = fun(_) -> true = ets:insert(smp_insert,{random:uniform(10000)})
4787
5110
            end,
4796
5119
    only_if_smp(fun()->smp_fixed_delete_do() end).
4797
5120
 
4798
5121
smp_fixed_delete_do() ->
4799
 
    T = ets:new(foo,[public,{write_concurrency,true}]),
 
5122
    T = ets_new(foo,[public,{write_concurrency,true}]),
4800
5123
    %%Mem = ets:info(T,memory),
4801
5124
    NumOfObjs = 100000,
4802
5125
    filltabint(T,NumOfObjs),
4832
5155
smp_unfix_fix_do() ->
4833
5156
    process_flag(scheduler,1),
4834
5157
    Parent = self(),
4835
 
    T = ets:new(foo,[public,{write_concurrency,true}]),
 
5158
    T = ets_new(foo,[public,{write_concurrency,true}]),
4836
5159
    %%Mem = ets:info(T,memory),
4837
5160
    NumOfObjs = 100000,
4838
5161
    Deleted = 50000,    
4892
5215
    %% Bug scenario: One process segv while reading the table because another
4893
5216
    %% process is doing unfix without write-lock at the end of a trapping match_object.
4894
5217
    process_flag(scheduler,1),
4895
 
    T = ets:new(foo,[public, {write_concurrency,WC}]),
 
5218
    T = ets_new(foo,[public, {write_concurrency,WC}]),
4896
5219
    NumOfObjs = 3000,  %% Need more than 1000 live objects for match_object to trap one time
4897
5220
    Deleted = NumOfObjs div 2,
4898
5221
    filltabint(T,NumOfObjs),
5004
5327
               end.
5005
5328
    
5006
5329
                  
5007
 
    
5008
 
    
 
5330
otp_8732(doc) -> ["ets:select on a tree with NIL key object"];
 
5331
otp_8732(Config) when is_list(Config) ->
 
5332
    Tab = ets_new(noname,[ordered_set]),
 
5333
    filltabstr(Tab,999),
 
5334
    ets:insert(Tab,{[],"nasty NIL object"}),
 
5335
    ?line [] = ets:match(Tab,{'_',nomatch}), %% Will hang if bug not fixed
 
5336
    ok.
 
5337
 
5009
5338
 
5010
5339
smp_select_delete(suite) -> [];
5011
5340
smp_select_delete(doc) ->
5012
5341
    ["Run concurrent select_delete (and inserts) on same table."];
5013
5342
smp_select_delete(Config) when is_list(Config) ->
5014
 
    T = ets:new(smp_select_delete,[named_table,public,{write_concurrency,true}]),
 
5343
    T = ets_new(smp_select_delete,[named_table,public,{write_concurrency,true}]),
5015
5344
    Mod = 17,
5016
5345
    Zeros = erlang:make_tuple(Mod,0),
5017
5346
    InitF = fun(_) -> Zeros end,
5064
5393
    ?line false = ets:info(T,fixed),
5065
5394
    ets:delete(T).
5066
5395
 
 
5396
types(doc) -> ["Test different types"];
 
5397
types(Config) when is_list(Config) ->
 
5398
    init_externals(),
 
5399
    repeat_for_opts(types_do,[[set,ordered_set],compressed]).
 
5400
 
 
5401
types_do(Opts) ->
 
5402
    EtsMem = etsmem(),
 
5403
    ?line T = ets_new(xxx,Opts),
 
5404
    Fun = fun(Term) ->
 
5405
            ets:insert(T,{Term}),
 
5406
            ?line [{Term}] = ets:lookup(T,Term),
 
5407
            ets:insert(T,{Term,xxx}),
 
5408
            ?line [{Term,xxx}] = ets:lookup(T,Term),
 
5409
            ets:insert(T,{Term,"xxx"}),
 
5410
            ?line [{Term,"xxx"}] = ets:lookup(T,Term),
 
5411
            ets:insert(T,{xxx,Term}),
 
5412
            ?line [{xxx,Term}] = ets:lookup(T,xxx),
 
5413
            ets:insert(T,{"xxx",Term}),
 
5414
            ?line [{"xxx",Term}] = ets:lookup(T,"xxx"),
 
5415
            ets:delete_all_objects(T),
 
5416
            ?line 0 = ets:info(T,size)
 
5417
          end,
 
5418
    test_terms(Fun, strict),
 
5419
    ets:delete(T),
 
5420
    ?line verify_etsmem(EtsMem).
 
5421
 
 
5422
 
 
5423
 
 
5424
 
 
5425
%
 
5426
% Utility functions:
 
5427
%
 
5428
 
5067
5429
add_lists(L1,L2) ->     
5068
5430
    add_lists(L1,L2,[]).
5069
5431
add_lists([],[],Acc) ->
5128
5490
my_tab_to_list(Ts,Key, Acc) ->
5129
5491
    my_tab_to_list(Ts,ets:next(Ts,Key),[ets:lookup(Ts, Key)| Acc]).
5130
5492
 
 
5493
wait_for_all_schedulers_online_to_execute() ->
 
5494
    PMs = lists:map(fun (Sched) ->
 
5495
                            spawn_opt(fun () -> ok end,
 
5496
                                      [monitor, {scheduler, Sched}])
 
5497
                    end,
 
5498
                    lists:seq(1,erlang:system_info(schedulers_online))),
 
5499
    lists:foreach(fun ({P, M}) ->
 
5500
                          receive
 
5501
                              {'DOWN', M, process, P, _} -> ok
 
5502
                          end
 
5503
                  end,
 
5504
                  PMs),
 
5505
    ok.
 
5506
 
5131
5507
etsmem() ->
 
5508
    %% Wait until it is guaranteed that all already scheduled
 
5509
    %% deallocations of DbTable structures have completed.
 
5510
    wait_for_all_schedulers_online_to_execute(),
 
5511
 
 
5512
    AllTabs = lists:map(fun(T) -> {T,ets:info(T,name),ets:info(T,size),
 
5513
                                   ets:info(T,memory),ets:info(T,type)} 
 
5514
                        end, ets:all()),
 
5515
    Mem =
5132
5516
    {try erlang:memory(ets) catch error:notsup -> notsup end,
5133
5517
     case erlang:system_info({allocator,ets_alloc}) of
5134
5518
         false -> undefined;
5147
5531
                       {value,{_,BlSz,_,_}} = lists:keysearch(blocks_size, 1, L),
5148
5532
                       {Bl0+Bl,BlSz0+BlSz}
5149
5533
               end, {0,0}, MSBCS)
5150
 
     end}.
 
5534
     end},
 
5535
     {Mem,AllTabs}.
5151
5536
 
5152
 
verify_etsmem(MemInfo) ->
 
5537
verify_etsmem({MemInfo,AllTabs}) ->
5153
5538
    wait_for_test_procs(),
5154
5539
    case etsmem() of
5155
 
        MemInfo ->
 
5540
        {MemInfo,_} ->
5156
5541
            io:format("Ets mem info: ~p", [MemInfo]),
5157
5542
            case MemInfo of
5158
5543
                {ErlMem,EtsAlloc} when ErlMem == notsup; EtsAlloc == undefined ->
5161
5546
                _ ->
5162
5547
                    ok
5163
5548
            end;
5164
 
        Other ->
 
5549
        {MemInfo2, AllTabs2} ->
5165
5550
            io:format("Expected: ~p", [MemInfo]),
5166
 
            io:format("Actual:   ~p", [Other]),
 
5551
            io:format("Actual:   ~p", [MemInfo2]),
 
5552
            io:format("Changed tables before: ~p\n",[AllTabs -- AllTabs2]),
 
5553
            io:format("Changed tables after: ~p\n", [AllTabs2 -- AllTabs]),
5167
5554
            ?t:fail()
5168
5555
    end.
5169
5556
 
 
5557
 
5170
5558
start_loopers(N, Prio, Fun, State) ->
5171
5559
    lists:map(fun (_) ->
5172
5560
                      my_spawn_opt(fun () -> looper(Fun, State) end,
5271
5659
        {false,Ret} -> Ret
5272
5660
    end.
5273
5661
 
 
5662
%% Some (but not all) permutations of List
 
5663
repeat_for_permutations(Fun, List) ->
 
5664
    repeat_for_permutations(Fun, List, length(List)-1).
 
5665
repeat_for_permutations(Fun, List, 0) ->
 
5666
    Fun(List);
 
5667
repeat_for_permutations(Fun, List, N) ->
 
5668
    {A,B} = lists:split(N, List),
 
5669
    L1 = B++A,
 
5670
    L2 = lists:reverse(L1),
 
5671
    L3 = B++lists:reverse(A),
 
5672
    L4 = lists:reverse(B)++A,
 
5673
    Fun(L1), Fun(L2), Fun(L3), Fun(L4),
 
5674
    repeat_for_permutations(Fun, List, N-1).
 
5675
 
5274
5676
receive_any() ->
5275
5677
    receive M ->
5276
5678
            io:format("Process ~p got msg ~p\n", [self(),M]),
5326
5728
        {true,_} -> Func()
5327
5729
    end.
5328
5730
 
 
5731
%% Copy-paste from emulator/test/binary_SUITE.erl
 
5732
-define(heap_binary_size, 64).
 
5733
test_terms(Test_Func, Mode) ->
 
5734
    garbage_collect(),
 
5735
    ?line Pib0 = process_info(self(),binary),
 
5736
 
 
5737
    ?line Test_Func(atom),
 
5738
    ?line Test_Func(''),
 
5739
    ?line Test_Func('a'),
 
5740
    ?line Test_Func('ab'),
 
5741
    ?line Test_Func('abc'),
 
5742
    ?line Test_Func('abcd'),
 
5743
    ?line Test_Func('abcde'),
 
5744
    ?line Test_Func('abcdef'),
 
5745
    ?line Test_Func('abcdefg'),
 
5746
    ?line Test_Func('abcdefgh'),
 
5747
 
 
5748
    ?line Test_Func(fun() -> ok end),
 
5749
    X = id([a,{b,c},c]),
 
5750
    Y = id({x,y,z}),
 
5751
    Z = id(1 bsl 8*257),
 
5752
    ?line Test_Func(fun() -> X end),
 
5753
    ?line Test_Func(fun() -> {X,Y} end),
 
5754
    ?line Test_Func([fun() -> {X,Y,Z} end,
 
5755
              fun() -> {Z,X,Y} end,
 
5756
              fun() -> {Y,Z,X} end]),
 
5757
 
 
5758
    ?line Test_Func({trace_ts,{even_bigger,{some_data,fun() -> ok end}},{1,2,3}}),
 
5759
    ?line Test_Func({trace_ts,{even_bigger,{some_data,<<1,2,3,4,5,6,7,8,9,10>>}},
 
5760
              {1,2,3}}),
 
5761
 
 
5762
    ?line Test_Func(1),
 
5763
    ?line Test_Func(42),
 
5764
    ?line Test_Func(-23),
 
5765
    ?line Test_Func(256),
 
5766
    ?line Test_Func(25555),
 
5767
    ?line Test_Func(-3333),
 
5768
 
 
5769
    ?line Test_Func(1.0),
 
5770
 
 
5771
    ?line Test_Func(183749783987483978498378478393874),
 
5772
    ?line Test_Func(-37894183749783987483978498378478393874),
 
5773
    Very_Big = very_big_num(),
 
5774
    ?line Test_Func(Very_Big),
 
5775
    ?line Test_Func(-Very_Big+1),
 
5776
 
 
5777
    ?line Test_Func([]),
 
5778
    ?line Test_Func("abcdef"),
 
5779
    ?line Test_Func([a, b, 1, 2]),
 
5780
    ?line Test_Func([a|b]),
 
5781
 
 
5782
    ?line Test_Func({}),
 
5783
    ?line Test_Func({1}),
 
5784
    ?line Test_Func({a, b}),
 
5785
    ?line Test_Func({a, b, c}),
 
5786
    ?line Test_Func(list_to_tuple(lists:seq(0, 255))),
 
5787
    ?line Test_Func(list_to_tuple(lists:seq(0, 256))),
 
5788
 
 
5789
    ?line Test_Func(make_ref()),
 
5790
    ?line Test_Func([make_ref(), make_ref()]),
 
5791
 
 
5792
    ?line Test_Func(make_port()),
 
5793
 
 
5794
    ?line Test_Func(make_pid()),
 
5795
    ?line Test_Func(make_ext_pid()),
 
5796
    ?line Test_Func(make_ext_port()),
 
5797
    ?line Test_Func(make_ext_ref()),
 
5798
 
 
5799
    Bin0 = list_to_binary(lists:seq(0, 14)),
 
5800
    ?line Test_Func(Bin0),
 
5801
    Bin1 = list_to_binary(lists:seq(0, ?heap_binary_size)),
 
5802
    ?line Test_Func(Bin1),
 
5803
    Bin2 = list_to_binary(lists:seq(0, ?heap_binary_size+1)),
 
5804
    ?line Test_Func(Bin2),
 
5805
    Bin3 = list_to_binary(lists:seq(0, 255)),
 
5806
    garbage_collect(),
 
5807
    Pib = process_info(self(),binary),
 
5808
    ?line Test_Func(Bin3),
 
5809
    garbage_collect(),
 
5810
    case Mode of
 
5811
        strict -> ?line Pib = process_info(self(),binary);
 
5812
        skip_refc_check -> ok
 
5813
    end,
 
5814
 
 
5815
    ?line Test_Func(make_unaligned_sub_binary(Bin0)),
 
5816
    ?line Test_Func(make_unaligned_sub_binary(Bin1)),
 
5817
    ?line Test_Func(make_unaligned_sub_binary(Bin2)),
 
5818
    ?line Test_Func(make_unaligned_sub_binary(Bin3)),
 
5819
 
 
5820
    ?line Test_Func(make_sub_binary(lists:seq(42, 43))),
 
5821
    ?line Test_Func(make_sub_binary([42,43,44])),
 
5822
    ?line Test_Func(make_sub_binary([42,43,44,45])),
 
5823
    ?line Test_Func(make_sub_binary([42,43,44,45,46])),
 
5824
    ?line Test_Func(make_sub_binary([42,43,44,45,46,47])),
 
5825
    ?line Test_Func(make_sub_binary([42,43,44,45,46,47,48])),
 
5826
    ?line Test_Func(make_sub_binary(lists:seq(42, 49))),
 
5827
    ?line Test_Func(make_sub_binary(lists:seq(0, 14))),
 
5828
    ?line Test_Func(make_sub_binary(lists:seq(0, ?heap_binary_size))),
 
5829
    ?line Test_Func(make_sub_binary(lists:seq(0, ?heap_binary_size+1))),
 
5830
    ?line Test_Func(make_sub_binary(lists:seq(0, 255))),
 
5831
 
 
5832
    ?line Test_Func(make_unaligned_sub_binary(lists:seq(42, 43))),
 
5833
    ?line Test_Func(make_unaligned_sub_binary([42,43,44])),
 
5834
    ?line Test_Func(make_unaligned_sub_binary([42,43,44,45])),
 
5835
    ?line Test_Func(make_unaligned_sub_binary([42,43,44,45,46])),
 
5836
    ?line Test_Func(make_unaligned_sub_binary([42,43,44,45,46,47])),
 
5837
    ?line Test_Func(make_unaligned_sub_binary([42,43,44,45,46,47,48])),
 
5838
    ?line Test_Func(make_unaligned_sub_binary(lists:seq(42, 49))),
 
5839
    ?line Test_Func(make_unaligned_sub_binary(lists:seq(0, 14))),
 
5840
    ?line Test_Func(make_unaligned_sub_binary(lists:seq(0, ?heap_binary_size))),
 
5841
    ?line Test_Func(make_unaligned_sub_binary(lists:seq(0, ?heap_binary_size+1))),
 
5842
    ?line Test_Func(make_unaligned_sub_binary(lists:seq(0, 255))),
 
5843
 
 
5844
    %% Bit level binaries.
 
5845
    ?line Test_Func(<<1:1>>),
 
5846
    ?line Test_Func(<<2:2>>),
 
5847
    ?line Test_Func(<<42:10>>),
 
5848
    ?line Test_Func(list_to_bitstring([<<5:6>>|lists:seq(0, 255)])),
 
5849
 
 
5850
    ?line Test_Func(F = fun(A) -> 42*A end),
 
5851
    ?line Test_Func(lists:duplicate(32, F)),
 
5852
 
 
5853
    ?line Test_Func(FF = fun binary_SUITE:all/1),
 
5854
    ?line Test_Func(lists:duplicate(32, FF)),
 
5855
 
 
5856
    garbage_collect(),
 
5857
    case Mode of
 
5858
        strict -> ?line Pib0 = process_info(self(),binary);
 
5859
        skip_refc_check -> ok
 
5860
    end,
 
5861
    ok.
 
5862
 
 
5863
 
 
5864
id(I) -> I.
 
5865
 
 
5866
very_big_num() ->
 
5867
    very_big_num(33, 1).
 
5868
 
 
5869
very_big_num(Left, Result) when Left > 0 ->
 
5870
    ?line very_big_num(Left-1, Result*256);
 
5871
very_big_num(0, Result) ->
 
5872
    ?line Result.
 
5873
 
 
5874
make_port() ->
 
5875
    ?line open_port({spawn, efile}, [eof]).
 
5876
 
 
5877
make_pid() ->
 
5878
    ?line spawn_link(?MODULE, sleeper, []).
 
5879
 
 
5880
sleeper() ->
 
5881
    ?line receive after infinity -> ok end.
 
5882
 
 
5883
make_ext_pid() ->
 
5884
    {Pid, _, _} = get(externals),
 
5885
    Pid.
 
5886
 
 
5887
make_ext_port() ->
 
5888
    {_, Port, _} = get(externals),
 
5889
    Port.
 
5890
make_ext_ref() ->
 
5891
    {_, _, Ref} = get(externals),
 
5892
    Ref.
 
5893
 
 
5894
init_externals() ->
 
5895
    case get(externals) of
 
5896
        undefined ->
 
5897
            SysDistSz = ets:info(sys_dist,size),
 
5898
            ?line Pa = filename:dirname(code:which(?MODULE)),
 
5899
            ?line {ok, Node} = test_server:start_node(plopp, slave, [{args, " -pa " ++ Pa}]),
 
5900
            ?line Res = case rpc:call(Node, ?MODULE, rpc_externals, []) of
 
5901
                            {badrpc, {'EXIT', E}} ->
 
5902
                                test_server:fail({rpcresult, E});
 
5903
                            R -> R
 
5904
                        end,
 
5905
            ?line test_server:stop_node(Node),
 
5906
 
 
5907
            %% Wait for table 'sys_dist' to stabilize
 
5908
            repeat_while(fun() ->
 
5909
                                 case ets:info(sys_dist,size) of
 
5910
                                     SysDistSz -> false;
 
5911
                                     Sz ->
 
5912
                                         io:format("Waiting for sys_dist to revert size from ~p to size ~p\n",
 
5913
                                                   [Sz, SysDistSz]),
 
5914
                                         receive after 1000 -> true end
 
5915
                                 end
 
5916
                         end),
 
5917
            put(externals, Res);
 
5918
 
 
5919
        {_,_,_} -> ok
 
5920
    end.
 
5921
 
 
5922
rpc_externals() ->
 
5923
    {self(), make_port(), make_ref()}.
 
5924
 
 
5925
make_sub_binary(Bin) when is_binary(Bin) ->
 
5926
    {_,B} = split_binary(list_to_binary([0,1,3,Bin]), 3),
 
5927
    B;
 
5928
make_sub_binary(List) ->
 
5929
    make_sub_binary(list_to_binary(List)).
 
5930
 
 
5931
make_unaligned_sub_binary(Bin0) when is_binary(Bin0) ->
 
5932
    Bin1 = <<0:3,Bin0/binary,31:5>>,
 
5933
    Sz = size(Bin0),
 
5934
    <<0:3,Bin:Sz/binary,31:5>> = id(Bin1),
 
5935
    Bin;
 
5936
make_unaligned_sub_binary(List) ->
 
5937
    make_unaligned_sub_binary(list_to_binary(List)).
5329
5938
 
5330
5939
%% Repeat test function with different combination of table options
5331
5940
%%       
5332
5941
repeat_for_opts(F) ->
5333
 
    repeat_for_opts(F, [write_concurrency]).
 
5942
    repeat_for_opts(F, [write_concurrency, read_concurrency, compressed]).
5334
5943
 
5335
5944
repeat_for_opts(F, OptGenList) when is_atom(F) ->
5336
5945
    repeat_for_opts(fun(Opts) -> ?MODULE:F(Opts) end, OptGenList);
 
5946
repeat_for_opts({F,Args}, OptGenList) when is_atom(F) ->
 
5947
    repeat_for_opts(fun(Opts) -> ?MODULE:F(Opts,Args) end, OptGenList);
5337
5948
repeat_for_opts(F, OptGenList) ->
5338
5949
    repeat_for_opts(F, OptGenList, []).
5339
5950
 
5340
5951
repeat_for_opts(F, [], Acc) ->
5341
 
    lists:map(fun(Opts) -> 
5342
 
                      io:format("Calling with options ~p\n",[Opts]),
5343
 
                      F(Opts)
5344
 
              end, Acc);
 
5952
    lists:map(fun(Opts) ->
 
5953
                    OptList = lists:filter(fun(E) -> E =/= void end, Opts),
 
5954
                    io:format("Calling with options ~p\n",[OptList]),
 
5955
                            F(OptList)
 
5956
                  end, Acc);
5345
5957
repeat_for_opts(F, [OptList | Tail], []) when is_list(OptList) ->
5346
5958
    repeat_for_opts(F, Tail, [[Opt] || Opt <- OptList]);
5347
5959
repeat_for_opts(F, [OptList | Tail], AccList) when is_list(OptList) ->
5350
5962
    repeat_for_opts(F, [repeat_for_opts_atom2list(Atom) | Tail ], AccList).
5351
5963
 
5352
5964
repeat_for_opts_atom2list(all_types) -> [set,ordered_set,bag,duplicate_bag];
5353
 
repeat_for_opts_atom2list(write_concurrency) -> [{write_concurrency,false},{write_concurrency,true}].
5354
 
 
 
5965
repeat_for_opts_atom2list(write_concurrency) -> [{write_concurrency,false},{write_concurrency,true}];
 
5966
repeat_for_opts_atom2list(read_concurrency) -> [{read_concurrency,false},{read_concurrency,true}];
 
5967
repeat_for_opts_atom2list(compressed) -> [compressed,void].
5355
5968
    
 
5969
ets_new(Name, Opts) ->
 
5970
    %%ets:new(Name, [compressed | Opts]).
 
5971
    ets:new(Name, Opts).