~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

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

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
3
%% 
4
 
%% Copyright Ericsson AB 2001-2010. All Rights Reserved.
 
4
%% Copyright Ericsson AB 2001-2011. All Rights Reserved.
5
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
21
21
%% Dets files, implementation part. This module handles version 9.
22
22
%% To be called from dets.erl only.
23
23
 
24
 
-export([constants/0, mark_dirty/1, read_file_header/2,
 
24
-export([mark_dirty/1, read_file_header/2,
25
25
         check_file_header/2, do_perform_save/1, initiate_file/11,
26
26
         prep_table_copy/9, init_freelist/2, fsck_input/4,
27
27
         bulk_input/3, output_objs/4, bchunk_init/2,
70
70
%%    16     MD5-sum for the 44 plus 112 bytes before the MD5-sum.
71
71
%%           (FreelistsPointer, Cookie and ClosedProperly are not digested.)
72
72
%%    128    Reserved for future versions. Initially zeros.
 
73
%%           Version 9(d), introduced in R15A, has instead:
 
74
%%    112    28 counters for the buddy system sizes (as for 9(b)).
 
75
%%    16     MD5-sum for the 44 plus 112 bytes before the MD5-sum.
 
76
%%           (FreelistsPointer, Cookie and ClosedProperly are not digested.)
 
77
%%    4      Base of the buddy system.
 
78
%%           0 (zero) if the base is equal to ?BASE. Compatible with R14B.
 
79
%%           File size at the end of the file is RealFileSize - Base.
 
80
%%           The reason for modifying file size is that when a file created
 
81
%%           by R15 is read by R14 a repair takes place immediately, which
 
82
%%           is acceptable when downgrading.
 
83
%%    124    Reserved for future versions. Initially zeros.
73
84
%%  ---
74
85
%%  ------------------ end of file header
75
86
%%    4*256  SegmentArray Pointers.
86
97
%%  -----------------------------
87
98
%%    ???    Free lists
88
99
%%  -----------------------------
89
 
%%    4      File size, in bytes. 
 
100
%%    4      File size, in bytes. See 9(d) obove.
90
101
 
91
102
%%  Before we can find an object we must find the slot where the
92
103
%%  object resides. Each slot is a (possibly empty) list (or chain) of
177
188
%%% File header
178
189
%%%
179
190
 
180
 
-define(RESERVED, 128).        % Reserved for future use.
 
191
-define(RESERVED, 124).        % Reserved for future use.
181
192
 
182
193
-define(COLL_CNTRS, (28*4)).     % Counters for the buddy system.
183
194
-define(MD5SZ, 16).
 
195
-define(FL_BASE, 4).
184
196
 
185
 
-define(HEADSZ, 
186
 
        56+?COLL_CNTRS+?MD5SZ). % The size of the file header, in bytes,
187
 
                                % not including the reserved part.
 
197
-define(HEADSZ, 56+?COLL_CNTRS  % The size of the file header, in bytes,
 
198
            +?MD5SZ+?FL_BASE).  % not including the reserved part.
188
199
-define(HEADEND, (?HEADSZ+?RESERVED)). 
189
200
                               % End of header and reserved area.
190
201
-define(SEGSZ, 512).           % Size of a segment, in words. SZOBJP*SEGSZP.
270
281
%%-define(DEBUGF(X,Y), io:format(X, Y)).
271
282
-define(DEBUGF(X,Y), void).
272
283
 
273
 
%% {Bump}
274
 
constants() ->
275
 
    {?BUMP, ?BASE}.
276
 
 
277
284
%% -> ok | throw({NewHead,Error})
278
285
mark_dirty(Head) ->
279
286
    Dirty = [{?CLOSED_PROPERLY_POS, <<?NOT_PROPERLY_CLOSED:32>>}],
356
363
      cache = dets_utils:new_cache(CacheSz),
357
364
      version = ?FILE_FORMAT_VERSION,
358
365
      bump = ?BUMP,
359
 
      base = ?BASE,
 
366
      base = ?BASE, % to be overwritten
360
367
      mod = ?MODULE
361
368
     },
362
369
 
378
385
    {Head1, Ws1} = init_parts(Head0, 0, no_parts(Next), Zero, []),
379
386
    NoSegs = no_segs(Next),
380
387
 
381
 
    {Head, WsI, WsP} = init_segments(Head1, 0, NoSegs, Zero, [], []),
 
388
    {Head2, WsI, WsP} = init_segments(Head1, 0, NoSegs, Zero, [], []),
382
389
    Ws2 = if
383
390
              DoInitSegments -> WsP ++ WsI;
384
391
              true -> WsP
385
392
         end,
386
393
    dets_utils:pwrite(Fd, Fname, [W0 | lists:append(Ws1) ++ Ws2]),
387
 
    true = hash_invars(Head),
 
394
    true = hash_invars(Head2),
 
395
    %% The allocations that have been made so far (parts, segments)
 
396
    %% are permanent; the table will never shrink. Therefore the base
 
397
    %% of the Buddy system can be set to the first free object.
 
398
    %% This is used in allocate_all(), see below.
 
399
    {_, Where, _} = dets_utils:alloc(Head2, ?BUMP),
 
400
    NewFtab = dets_utils:init_alloc(Where),
 
401
    Head = Head2#head{freelists = NewFtab, base = Where},
388
402
    {ok, Head}.
389
403
 
390
404
%% Returns a power of two not less than 256.
451
465
      Version:32,    M:32,       Next:32,       Kp:32,
452
466
      NoObjects:32,  NoKeys:32,  MinNoSlots:32, MaxNoSlots:32,
453
467
      HashMethod:32, N:32, NoCollsB:?COLL_CNTRS/binary, 
454
 
      MD5:?MD5SZ/binary>> = Bin,
455
 
    <<_:12/binary,MD5DigestedPart:(?HEADSZ-?MD5SZ-12)/binary,_/binary>> = Bin,
 
468
      MD5:?MD5SZ/binary, FlBase:32>> = Bin,
 
469
    <<_:12/binary,MD5DigestedPart:(?HEADSZ-?MD5SZ-?FL_BASE-12)/binary,
 
470
      _/binary>> = Bin,
456
471
    {ok, EOF} = dets_utils:position_close(Fd, FileName, eof),
457
472
    {ok, <<FileSize:32>>} = dets_utils:pread_close(Fd, FileName, EOF-4, 4),
458
473
    {CL, <<>>} = lists:foldl(fun(LSz, {Acc,<<NN:32,R/binary>>}) -> 
468
483
            true ->
469
484
                lists:reverse(CL)
470
485
        end,
471
 
                             
 
486
    Base = case FlBase of
 
487
               0 -> ?BASE;
 
488
               _ -> FlBase
 
489
           end,
472
490
    FH = #fileheader{freelist = FreeList,
 
491
                     fl_base = Base,
473
492
                     cookie = Cookie,
474
493
                     closed_properly = CP,
475
494
                     type = dets_utils:code_to_type(Type2),
486
505
                     read_md5 = MD5,
487
506
                     has_md5 = <<0:?MD5SZ/unit:8>> =/= MD5,
488
507
                     md5 = erlang:md5(MD5DigestedPart),
489
 
                     trailer = FileSize,
 
508
                     trailer = FileSize + FlBase,
490
509
                     eof = EOF,
491
510
                     n = N,
492
511
                     mod = ?MODULE},
544
563
              version = ?FILE_FORMAT_VERSION,
545
564
              mod = ?MODULE,
546
565
              bump = ?BUMP,
547
 
              base = ?BASE},
 
566
              base = FH#fileheader.fl_base},
548
567
            {ok, H, ExtraInfo};
549
568
        Error ->
550
569
            Error
1185
1204
    write_loop(Head, BytesToWrite, SmallBin).
1186
1205
 
1187
1206
%% By allocating bigger objects before smaller ones, holes in the
1188
 
%% buddy system memory map are avoided. Unfortunately, the segments
1189
 
%% are always allocated first, so if there are objects bigger than a
1190
 
%% segment, there is a hole to handle. (Haven't considered placing the
1191
 
%% segments among other objects of the same size.)
 
1207
%% buddy system memory map are avoided.
1192
1208
allocate_all_objects(Head, SizeT) ->
1193
1209
    DTL = lists:reverse(lists:keysort(1, ets:tab2list(SizeT))),
1194
1210
    MaxSz = element(1, hd(DTL)),
1195
 
    SegSize = ?ACTUAL_SEG_SIZE,
1196
 
    {Head1, HSz, HN, HA} = alloc_hole(MaxSz, Head, SegSize),
1197
 
    {Head2, NL} = allocate_all(Head1, DTL, []),
 
1211
    {Head1, NL} = allocate_all(Head, DTL, []),
1198
1212
    %% Find the position that will be the end of the file by allocating
1199
1213
    %% a minimal object.
1200
 
    {_Head, EndOfFile, _} = dets_utils:alloc(Head2, ?BUMP),
1201
 
    Head3 = free_hole(Head2, HSz, HN, HA),
1202
 
    NewHead = Head3#head{maxobjsize = max_objsize(Head3#head.no_collections)},
 
1214
    {_Head, EndOfFile, _} = dets_utils:alloc(Head1, ?BUMP),
 
1215
    NewHead = Head1#head{maxobjsize = max_objsize(Head1#head.no_collections)},
1203
1216
    {NewHead, NL, MaxSz, EndOfFile}.
1204
1217
 
1205
 
alloc_hole(LSize, Head, SegSz) when ?POW(LSize-1) > SegSz ->
1206
 
    Size = ?POW(LSize-1),
1207
 
    {_, SegAddr, _} = dets_utils:alloc(Head, adjsz(SegSz)),
1208
 
    {_, Addr, _} = dets_utils:alloc(Head, adjsz(Size)),
1209
 
    N = (Addr - SegAddr) div SegSz,
1210
 
    Head1 = dets_utils:alloc_many(Head, SegSz, N, SegAddr),
1211
 
    {Head1, SegSz, N, SegAddr};
1212
 
alloc_hole(_MaxSz, Head, _SegSz) ->
1213
 
    {Head, 0, 0, 0}.
1214
 
 
1215
 
free_hole(Head, _Size, 0, _Addr) ->
1216
 
    Head;
1217
 
free_hole(Head, Size, N, Addr) ->
1218
 
    {Head1, _} = dets_utils:free(Head, Addr, adjsz(Size)),
1219
 
    free_hole(Head1, Size, N-1, Addr+Size).
1220
 
 
1221
1218
%% One (temporary) file for each buddy size, write all objects of that
1222
1219
%% size to the file.
 
1220
%%
 
1221
%% Before R15 a "hole" was needed before the first bucket if the size
 
1222
%% of the biggest bucket was greater than the size of a segment. The
 
1223
%% hole proved to be a problem with almost full tables with huge
 
1224
%% buckets. Since R15 the hole is no longer needed due to the fact
 
1225
%% that the base of the Buddy system is flexible.
1223
1226
allocate_all(Head, [{?FSCK_SEGMENT,_,Data,_}], L) ->
1224
1227
    %% And one file for the segments...
1225
1228
    %% Note that space for the array parts and the segments has
1593
1596
    H1 = H#head{freelists_p = FreeListsPointer},
1594
1597
    {FLW, FLSize} = free_lists_to_file(H1),
1595
1598
    FileSize = FreeListsPointer + FLSize + 4,
1596
 
    ok = dets_utils:write(H1, [FLW | <<FileSize:32>>]),
 
1599
    AdjustedFileSize = case H#head.base of
 
1600
                           ?BASE -> FileSize;
 
1601
                           Base -> FileSize - Base
 
1602
                       end,
 
1603
    ok = dets_utils:write(H1, [FLW | <<AdjustedFileSize:32>>]),
1597
1604
    FileHeader = file_header(H1, FreeListsPointer, ?CLOSED_PROPERLY),
1598
1605
    case dets_utils:debug_mode() of
1599
1606
        true -> 
1600
 
            TmpHead = H1#head{freelists = init_freelist(H1, true), 
1601
 
                              fixed = false},
 
1607
            TmpHead0 = init_freelist(H1#head{fixed = false}, true),
 
1608
            TmpHead = TmpHead0#head{base = H1#head.base},
1602
1609
            case 
1603
1610
                catch dets_utils:all_allocated_as_list(TmpHead)
1604
1611
                      =:= dets_utils:all_allocated_as_list(H1)
1605
 
                of
 
1612
            of
1606
1613
                true -> 
1607
1614
                    dets_utils:pwrite(H1, [{0, FileHeader}]);
1608
1615
                _ -> 
 
1616
                    throw(
1609
1617
                    dets_utils:corrupt_reason(H1, {failed_to_save_free_lists,
1610
1618
                                                   FreeListsPointer,
1611
1619
                                                   TmpHead#head.freelists,
1612
 
                                                   H1#head.freelists})
 
1620
                                                   H1#head.freelists}))
1613
1621
            end;
1614
1622
        false ->
1615
1623
            dets_utils:pwrite(H1, [{0, FileHeader}])
1648
1656
              true -> erlang:md5(DigH);
1649
1657
              false -> <<0:?MD5SZ/unit:8>>
1650
1658
          end,
1651
 
    [H1, DigH, MD5 | <<0:?RESERVED/unit:8>>].
 
1659
    Base = case Head#head.base of
 
1660
               ?BASE -> <<0:32>>;
 
1661
               FlBase -> <<FlBase:32>>
 
1662
           end,
 
1663
    [H1, DigH, MD5, Base | <<0:?RESERVED/unit:8>>].
1652
1664
 
1653
1665
%% Going through some trouble to avoid creating one single binary for
1654
1666
%% the free lists. If the free lists are huge, binary_to_term and
1695
1707
    case catch bin_to_tree([], H, start, FL, -1, []) of
1696
1708
        {'EXIT', _} ->
1697
1709
            throw({error, {bad_freelists, H#head.filename}});
1698
 
        Reply ->
1699
 
            Reply
 
1710
        Ftab ->
 
1711
            H#head{freelists = Ftab, base = ?BASE}
1700
1712
    end.
1701
1713
 
1702
1714
bin_to_tree(Bin, H, LastPos, Ftab, A0, L) ->