~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

Viewing changes to lib/stdlib/src/dets.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%% ``The contents of this file are subject to the Erlang Public License,
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
2
7
%% Version 1.1, (the "License"); you may not use this file except in
3
8
%% compliance with the License. You should have received a copy of the
4
9
%% Erlang Public License along with this software. If not, it can be
5
 
%% retrieved via the world wide web at http://www.erlang.org/.
 
10
%% retrieved online at http://www.erlang.org/.
6
11
%% 
7
12
%% Software distributed under the License is distributed on an "AS IS"
8
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
14
%% the License for the specific language governing rights and limitations
10
15
%% under the License.
11
16
%% 
12
 
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
13
 
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
14
 
%% AB. All Rights Reserved.''
15
 
%% 
16
 
%%     $Id $
 
17
%% %CopyrightEnd%
17
18
%%
18
19
-module(dets).
19
20
 
95
96
 
96
97
-include("dets.hrl").
97
98
 
 
99
-type object()   :: tuple().
 
100
-type pattern()  :: atom() | tuple().
 
101
-type tab_name() :: atom() | reference().
 
102
 
98
103
%%% This is the implementation of the mnesia file storage. Each (non
99
104
%%% ram-copy) table is maintained in a corresponding .DAT file. The
100
105
%%% dat file is organized as a segmented linear hashlist. The head of
190
195
 
191
196
add_user(Pid, Tab, Args) ->
192
197
    req(Pid, {add_user, Tab, Args}).
193
 
    
 
198
 
 
199
-spec all() -> [tab_name()].
 
200
 
194
201
all() ->
195
202
    dets_server:all().
196
203
 
 
204
-type cont() :: #dets_cont{}.
 
205
-spec bchunk(tab_name(), 'start' | cont()) ->
 
206
    {cont(), binary() | tuple()} | '$end_of_table' | {'error', term()}.
 
207
 
197
208
bchunk(Tab, start) ->
198
209
    badarg(treq(Tab, {bchunk_init, Tab}), [Tab, start]);
199
210
bchunk(Tab, #dets_cont{bin = eof, tab = Tab}) ->
203
214
bchunk(Tab, Term) ->
204
215
    erlang:error(badarg, [Tab, Term]).
205
216
 
 
217
-spec close(tab_name()) -> 'ok' | {'error', term()}.
 
218
 
206
219
close(Tab) ->  
207
220
    case dets_server:close(Tab) of
208
221
        badarg -> % Should not happen.
209
 
             {error, not_owner}; % Backwards compatibility...
 
222
            {error, not_owner}; % Backwards compatibility...
210
223
        Reply ->
211
224
            Reply
212
225
    end.
213
226
 
 
227
-spec delete(tab_name(), term()) -> 'ok' | {'error', term()}.
 
228
 
214
229
delete(Tab, Key) ->
215
230
    badarg(treq(Tab, {delete_key, [Key]}), [Tab, Key]).
216
231
 
 
232
-spec delete_all_objects(tab_name()) -> 'ok' | {'error', term()}.
 
233
 
217
234
delete_all_objects(Tab) ->
218
235
    case treq(Tab, delete_all_objects) of
219
236
        badarg ->
224
241
            Reply
225
242
    end.
226
243
 
 
244
-spec delete_object(tab_name(), object()) -> 'ok' | {'error', term()}.
 
245
 
227
246
delete_object(Tab, O) ->
228
247
    badarg(treq(Tab, {delete_object, [O]}), [Tab, O]).
229
248
 
245
264
      end
246
265
    end.
247
266
 
 
267
-spec first(tab_name()) -> term() | '$end_of_table'.
 
268
 
248
269
first(Tab) ->
249
270
    badarg_exit(treq(Tab, first), [Tab]).
250
271
 
 
272
-spec foldr(fun((object(), Acc) -> Acc), Acc, tab_name()) -> Acc | {'error', term()}.
 
273
 
251
274
foldr(Fun, Acc, Tab) ->
252
275
    foldl(Fun, Acc, Tab).
253
276
 
 
277
-spec foldl(fun((object(), Acc) -> Acc), Acc, tab_name()) -> Acc | {'error', term()}.
 
278
 
254
279
foldl(Fun, Acc, Tab) ->
255
280
    Ref = make_ref(),
256
281
    do_traverse(Fun, Acc, Tab, Ref).
257
282
 
 
283
-spec from_ets(tab_name(), ets:tab()) -> 'ok' | {'error', term()}.
 
284
 
258
285
from_ets(DTab, ETab) ->
259
286
    ets:safe_fixtable(ETab, true),
260
287
    Spec = ?PATTERN_TO_OBJECT_MATCH_SPEC('_'),
378
405
match(Term) ->
379
406
    erlang:error(badarg, [Term]).
380
407
 
 
408
-spec match_delete(tab_name(), pattern()) ->
 
409
        non_neg_integer() | 'ok' | {'error', term()}.
 
410
 
381
411
match_delete(Tab, Pat) ->
382
412
    badarg(match_delete(Tab, Pat, delete), [Tab, Pat]).
383
413
 
549
579
                end,
550
580
            qlc:table(TF, [{pre_fun, PreFun}, {post_fun, PostFun}, 
551
581
                           {info_fun, InfoFun}, {format_fun, FormatFun},
 
582
                           {key_equality, '=:='},
552
583
                           {lookup_fun, LookupFun}])
553
584
    end.
554
585
         
2432
2463
    EstNoSlots0 = file_no_things(FH),
2433
2464
    MinSlots = choose_no_slots(MinSlotsArg, MinSlotsFile),
2434
2465
    MaxSlots = choose_no_slots(MaxSlotsArg, MaxSlotsFile),
2435
 
    EstNoSlots = lists:min([MaxSlots, lists:max([MinSlots, EstNoSlots0])]),
 
2466
    EstNoSlots = erlang:min(MaxSlots, erlang:max(MinSlots, EstNoSlots0)),
2436
2467
    SlotNumbers = {MinSlots, EstNoSlots, MaxSlots},
2437
2468
    %% When repairing: We first try and sort on slots using MinSlots.
2438
2469
    %% If the number of objects (keys) turns out to be significantly