~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (1.1.13 upstream)
  • mto: (3.3.1 squeeze)
  • mto: This revision was merged to the branch mainline in revision 17.
  • Revision ID: james.westby@ubuntu.com-20090215164252-dxpjjuq108nz4noa
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
206
206
    end,
207
207
    case file:pwrite(Head#head.fptr, Bins) of
208
208
        ok ->
209
 
            try
210
 
                pwrite_check(Head#head.fptr, remove_overlaps(Bins))
211
 
            catch BadPos ->
212
 
                throw(corrupt_reason(Head, {bad_pwrite, BadPos, Bins}))
213
 
            end,
214
209
            {Head, ok};
215
210
        Error ->
216
211
            corrupt_file(Head, Error)
1045
1040
            ok
1046
1041
    end.
1047
1042
 
1048
 
%%% Extra code just for checking pwrite/2.
1049
 
%%% If you see this comment, you have have an inofficial version of
1050
 
%%% dets_utils.erl. Not for production!
1051
 
 
1052
 
pwrite_check(_Fd, []) ->
1053
 
    ok;
1054
 
pwrite_check(Fd, [{Pos,Bin0} | Bins]) ->
1055
 
    Bin = iolist_to_binary(Bin0),
1056
 
    case pread_n(Fd, Pos, byte_size(Bin)) of
1057
 
        Bin ->
1058
 
            pwrite_check(Fd, Bins);
1059
 
        Got ->
1060
 
            throw({Pos, Got})
1061
 
    end.
1062
 
 
1063
 
%% [{Pos,Bin}], Pos = integer() -> [{Pos,Bin}]
1064
 
%% Bin is some binary placed at position Pos. If B2 occurs after B1,
1065
 
%% then B2 overwrites B1, should they overlap. Overwritten parts are
1066
 
%% removed.
1067
 
remove_overlaps([]) -> [];
1068
 
remove_overlaps(L) ->
1069
 
    join_bins(remov(lists:sort(number_bins(L, 1, [])), [])).
1070
 
 
1071
 
number_bins([{P,B} | Es], I, L) ->
1072
 
    E = {P,P + bytes_size(B, 0),I,B},
1073
 
    number_bins(Es, I+1, [E | L]);
1074
 
number_bins([], _I, L) ->
1075
 
    L.
1076
 
 
1077
 
remov([{F1,T1,N1,B1} | Ss], L) ->
1078
 
    remov(Ss, F1, T1, N1, B1, L);
1079
 
remov([], L) ->
1080
 
    L.
1081
 
 
1082
 
remov([{F2,T2,N2,B2} | Ss], F1, T1, _N1, B1, L) when F2 >= T1 ->
1083
 
    remov(Ss, F2, T2, N2, B2, [{F1,T1,B1} | L]);
1084
 
remov([{F2,T2,N2,B2} | Ss], F1, T1, N1, _B1, L) when F1 == F2, T2>=T1, N2>N1 ->
1085
 
    remov(Ss, F2, T2, N2, B2, L);
1086
 
remov([{_F2,T2,N2,_B2} | Ss], F1, T1, N1, B1, L) when T1 >= T2, N1 > N2 ->
1087
 
    remov(Ss, F1, T1, N1, B1, L);
1088
 
remov(Ss = [{F2,_T2,N2,_B2} | _], F1, T1, N1, B1, L) when F1 < F2, N1 < N2 ->
1089
 
    Size = F2-F1,
1090
 
    {B, T} = split_bytes(B1, Size),
1091
 
    remov(place_bin(F2, T1, N1, T, Ss), [{F1,F2,B} | L]);
1092
 
remov([{F2,T2,N2,B2} | Ss], F1, T1, N1, B1, L) ->
1093
 
    Size = T1 - F2,
1094
 
    {_, T} = split_bytes(B2, Size),
1095
 
    NSs = place_bin(T1, T2, N2, T, Ss),
1096
 
    remov(NSs, F1, T1, N1, B1, L);
1097
 
remov([], F1, T1, _N1, B1, L) ->
1098
 
    [{F1,T1,B1} | L].
1099
 
 
1100
 
place_bin(F, T, N, B, Ss) ->
1101
 
    lists:merge([{F,T,N,B}], Ss).
1102
 
 
1103
 
join_bins([{F,_T,B} | Ss]) ->
1104
 
    join_bins(Ss, F, B, []);
1105
 
join_bins([]) ->
1106
 
    [].
1107
 
 
1108
 
join_bins([{F1,T1,B1} | Ss], F2, B2, L) when F2 == T1 ->
1109
 
    join_bins(Ss, F1, [B1 | B2], L);
1110
 
join_bins([{F1,T1,B1} | Ss], F2, B, L) when F2 > T1 ->
1111
 
    join_bins(Ss, F1, B1, [{F2,B} | L]);
1112
 
join_bins([], F, B, L) ->
1113
 
    [{F,B} | L].
1114
 
 
1115
 
bytes_size([], S) ->
1116
 
    S;
1117
 
bytes_size([B | Bs], S) ->
1118
 
    bytes_size(Bs, bytes_size(B, S));
1119
 
bytes_size(I, S) when is_integer(I) ->
1120
 
    S + 1;
1121
 
bytes_size(B, S) when is_binary(B) ->
1122
 
    S + byte_size(B).
1123
 
 
1124
 
split_bytes(B, Sz) when is_binary(B) ->
1125
 
    <<X:Sz/binary,Y/binary>> = B,
1126
 
    {X, Y};
1127
 
split_bytes(B, Sz) ->
1128
 
    split_bytes(list_to_binary(B), Sz).
1129
 
 
1130
 
%%% End of pwrite_check
1131
 
 
1132
1043
%%%-----------------------------------------------------------------
1133
1044
%%% These functions implement a B+ tree.
1134
1045
%%%-----------------------------------------------------------------