1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 1997-2018. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20-module(disk_log_1).
21
22%% Efficient file based log - implementation part
23
24-export([int_open/4, ext_open/4, logl/1, close/3, truncate/3, chunk/5,
25         sync/2, write_cache/2]).
26-export([mf_int_open/7, mf_int_log/3, mf_int_close/2, mf_int_inc/2,
27	 mf_ext_inc/2, mf_int_chunk/4, mf_int_chunk_step/3,
28	 mf_sync/1, mf_write_cache/1]).
29-export([mf_ext_open/7, mf_ext_log/3, mf_ext_close/2]).
30
31-export([print_index_file/1]).
32-export([read_index_file/1]).
33-export([read_size_file/1, read_size_file_version/1]).
34-export([chunk_read_only/5]).
35-export([mf_int_chunk_read_only/4]).
36-export([change_size_wrap/3]).
37-export([get_wrap_size/1]).
38-export([is_head/1]).
39-export([position/3, truncate_at/3, fwrite/4, fclose/2]).
40-export([set_quiet/1, is_quiet/0]).
41
42-compile({inline,[{scan_f2,7}]}).
43
44-import(lists, [concat/1, reverse/1, sum/1]).
45
46-include("disk_log.hrl").
47
48%%% At the head of a LOG file we have [?LOGMAGIC, ?OPENED | ?CLOSED].
49%%% Otherwise it's not a LOG file. Following that, the head, come the
50%%% logged items.
51%%%
52%%% There are four formats of wrap log files (so far). Only the size
53%%% file and the index file differ between versions between the first
54%%% three version. The fourth version 2(a), has some protection
55%%% against damaged item sizes.
56%%% Version 0: no "siz" file
57%%% Version 1: "siz" file, 4 byte sizes
58%%% Version 2: 8 byte sizes (support for large files)
59%%% Version 2(a): Change of the format of logged items:
60%%%               if the size of a term binary is greater than or equal to
61%%%               ?MIN_MD5_TERM, a logged item looks like
62%%%               <<Size:32, ?BIGMAGICHEAD:32, MD5:128, Term/binary>>,
63%%%               otherwise <<Size:32, ?BIGMAGICHEAD:32, Term/binary>>.
64
65%%%----------------------------------------------------------------------
66%%% API
67%%%----------------------------------------------------------------------
68
69%% -> {ok, NoBytes, NewFdC} | {Error, NewFdC}
70log(FdC, FileName, X) ->
71    {Bs, Size} = logl(X, [], 0),
72    case fwrite(FdC, FileName, Bs, Size) of
73	{ok, NewFdC} ->
74	    {ok, Size, NewFdC};
75	Error ->
76	    Error
77    end.
78
79-spec logl([binary()]) -> {iolist(), non_neg_integer()}.
80logl(X) ->
81    logl(X, [], 0).
82
83-dialyzer({no_improper_lists, logl/3}).
84logl([X | T], Bs, Size) ->
85    Sz = byte_size(X),
86    BSz = <<Sz:?SIZESZ/unit:8>>,
87    NBs = case Sz < ?MIN_MD5_TERM of
88              true ->
89                  [Bs, BSz, ?BIGMAGICHEAD | X];
90              false ->
91                  MD5 = erlang:md5(BSz),
92                  [Bs, BSz, ?BIGMAGICHEAD, MD5 | X]
93              end,
94    logl(T, NBs, Size + ?HEADERSZ + Sz);
95logl([], Bs, Size) ->
96    {Bs, Size}.
97
98%% -> {ok, NewFdC} | {Error, NewFdC}
99write_cache(#cache{fd = Fd, c = C}, FName) ->
100    erase(write_cache_timer_is_running),
101    write_cache(Fd, FName, C).
102
103%% -> {Reply, NewFdC}; Reply = ok | Error
104sync(FdC, FName) ->
105    fsync(FdC, FName).
106
107%% -> {Reply, NewFdC}; Reply = ok | Error
108truncate(FdC, FileName, Head) ->
109    Reply = truncate_at(FdC, FileName, ?HEADSZ),
110    case Reply of
111	{ok, _} when Head =:= none ->
112            Reply;
113	{ok, FdC1} ->
114	    {ok, B} = Head,
115	    case log(FdC1, FileName, [B]) of
116		{ok, _NoBytes, NewFdC} ->
117		    {ok, NewFdC};
118		Reply2 ->
119		    Reply2
120	    end;
121	_ ->
122	    Reply
123    end.
124
125%% -> {NewFdC, Reply}, Reply = {Cont, Binaries} | {error, Reason} | eof
126chunk(FdC, FileName, Pos, B, N) when is_binary(B) ->
127    true = byte_size(B) >= ?HEADERSZ,
128    do_handle_chunk(FdC, FileName, Pos, B, N);
129chunk(FdC, FileName, Pos, NoBytes, N) ->
130    MaxNoBytes = case NoBytes of
131                     [] -> ?MAX_CHUNK_SIZE;
132                     _ -> erlang:max(NoBytes, ?MAX_CHUNK_SIZE)
133                 end,
134    case read_chunk(FdC, FileName, Pos, MaxNoBytes) of
135	{NewFdC, {ok, Bin}} when byte_size(Bin) < ?HEADERSZ ->
136	    {NewFdC, {error, {corrupt_log_file, FileName}}};
137	{NewFdC, {ok, Bin}} when NoBytes =:= []; byte_size(Bin) >= NoBytes ->
138	    NewPos = Pos + byte_size(Bin),
139            do_handle_chunk(NewFdC, FileName, NewPos, Bin, N);
140	{NewFdC, {ok, _Bin}} ->
141	    {NewFdC, {error, {corrupt_log_file, FileName}}};
142	{NewFdC, eof} when is_integer(NoBytes) -> % "cannot happen"
143	    {NewFdC, {error, {corrupt_log_file, FileName}}};
144	Other -> % eof or error
145	    Other
146    end.
147
148do_handle_chunk(FdC, FileName, Pos, B, N) ->
149    case handle_chunk(B, Pos, N, []) of
150        corrupt ->
151            {FdC, {error, {corrupt_log_file, FileName}}};
152        {C, []} ->
153            chunk(FdC, FileName, C#continuation.pos, C#continuation.b, N);
154        C_Ack ->
155            {FdC, C_Ack}
156    end.
157
158handle_chunk(B, Pos, 0, Ack) when byte_size(B) >= ?HEADERSZ ->
159    {#continuation{pos = Pos, b = B}, Ack};
160handle_chunk(B= <<Size:?SIZESZ/unit:8, ?BIGMAGICINT:?MAGICSZ/unit:8,
161             Tail/binary>>, Pos, N, Ack) when Size < ?MIN_MD5_TERM ->
162    case Tail of
163	<<BinTerm:Size/binary, Tail2/binary>> ->
164	    %% The client calls binary_to_term/1.
165	    handle_chunk(Tail2, Pos, N-1, [BinTerm | Ack]);
166	_ ->
167	    BytesToRead = Size + ?HEADERSZ,
168            {#continuation{pos = Pos - byte_size(B), b = BytesToRead}, Ack}
169    end;
170handle_chunk(B= <<Size:?SIZESZ/unit:8, ?BIGMAGICINT:?MAGICSZ/unit:8,
171             Tail/binary>>, Pos, _N, Ack) -> % when Size >= ?MIN_MD5_TERM
172    MD5 = erlang:md5(<<Size:?SIZESZ/unit:8>>),
173    case Tail of
174        %% The requested object is always bigger than a chunk.
175        <<MD5:16/binary, Bin:Size/binary>> ->
176            {#continuation{pos = Pos, b = []}, [Bin | Ack]};
177        <<MD5:16/binary, _/binary>> ->
178            BytesToRead = Size + ?HEADERSZ + 16,
179            {#continuation{pos = Pos - byte_size(B), b = BytesToRead}, Ack};
180        _ when byte_size(Tail) >= 16 ->
181            corrupt;
182        _ ->
183            {#continuation{pos = Pos - byte_size(B), b = []}, Ack}
184    end;
185handle_chunk(B= <<Size:?SIZESZ/unit:8, ?MAGICINT:?MAGICSZ/unit:8, Tail/binary>>,
186	     Pos, N, Ack) ->
187    %% Version 2, before 2(a).
188    case Tail of
189	<<BinTerm:Size/binary, Tail2/binary>> ->
190	    handle_chunk(Tail2, Pos, N-1, [BinTerm | Ack]);
191	_ ->
192	    %% We read the whole thing into one binary, even if Size is huge.
193	    BytesToRead = Size + ?HEADERSZ,
194            {#continuation{pos = Pos - byte_size(B), b = BytesToRead}, Ack}
195    end;
196handle_chunk(B, _Pos, _N, _Ack) when byte_size(B) >= ?HEADERSZ ->
197    corrupt;
198handle_chunk(B, Pos, _N, Ack) ->
199    {#continuation{pos = Pos-byte_size(B), b = []}, Ack}.
200
201read_chunk(FdC, FileName, Pos, MaxBytes) ->
202    {FdC1, R} = pread(FdC, FileName, Pos + ?HEADSZ, MaxBytes),
203    case position(FdC1, FileName, eof) of
204	{ok, NewFdC, _Pos} ->
205	    {NewFdC, R};
206	{Error, NewFdC} ->
207	    {NewFdC, Error}
208    end.
209
210%% Used by wrap_log_reader.
211%% -> {NewFdC, Reply},
212%%    Reply = {Cont, Binaries, Bad} (Bad >= 0) | {error, Reason} | eof
213chunk_read_only(FdC = #cache{}, FileName, Pos, B, N) ->
214    do_chunk_read_only(FdC, FileName, Pos, B, N);
215chunk_read_only(Fd, FileName, Pos, B, N) ->
216    %% wrap_log_reader calling...
217    FdC = #cache{fd = Fd},
218    {_NFdC, Reply} = do_chunk_read_only(FdC, FileName, Pos, B, N),
219    Reply.
220
221do_chunk_read_only(FdC, FileName, Pos, B, N) when is_binary(B) ->
222    true = byte_size(B) >= ?HEADERSZ,
223    do_handle_chunk_ro(FdC, FileName, Pos, B, N);
224do_chunk_read_only(FdC, FileName, Pos, NoBytes, N) ->
225    MaxNoBytes = case NoBytes of
226                     [] -> ?MAX_CHUNK_SIZE;
227                     _ -> erlang:max(NoBytes, ?MAX_CHUNK_SIZE)
228                 end,
229    case read_chunk_ro(FdC, FileName, Pos, MaxNoBytes) of
230	{NewFdC, {ok, Bin}} when byte_size(Bin) < ?HEADERSZ ->
231	    NewCont = #continuation{pos = Pos+byte_size(Bin), b = []},
232	    {NewFdC, {NewCont, [], byte_size(Bin)}};
233	{NewFdC, {ok, Bin}} when NoBytes =:= []; byte_size(Bin) >= NoBytes ->
234	    NewPos = Pos + byte_size(Bin),
235	    do_handle_chunk_ro(NewFdC, FileName, NewPos, Bin, N);
236	{NewFdC, {ok, Bin}} ->
237	    NewCont = #continuation{pos = Pos+byte_size(Bin), b = []},
238	    {NewFdC, {NewCont, [], byte_size(Bin)-?HEADERSZ}};
239	{NewFdC, eof} when is_integer(NoBytes) -> % "cannot happen"
240	    {NewFdC, eof}; % what else?
241	Other ->
242	    Other
243    end.
244
245do_handle_chunk_ro(FdC, FileName, Pos, B, N) ->
246    case handle_chunk_ro(B, Pos, N, [], 0) of
247        {C, [], 0} ->
248            #continuation{pos = NewPos, b = NoBytes} = C,
249            do_chunk_read_only(FdC, FileName, NewPos, NoBytes, N);
250        C_Ack_Bad ->
251            {FdC, C_Ack_Bad}
252    end.
253
254handle_chunk_ro(B, Pos, 0, Ack, Bad) when byte_size(B) >= ?HEADERSZ ->
255    {#continuation{pos = Pos, b = B}, Ack, Bad};
256handle_chunk_ro(B= <<Size:?SIZESZ/unit:8, ?BIGMAGICINT:?MAGICSZ/unit:8,
257                Tail/binary>>, Pos, N, Ack, Bad) when Size < ?MIN_MD5_TERM ->
258    case Tail of
259	<<BinTerm:Size/binary, Tail2/binary>> ->
260	    handle_chunk_ro(Tail2, Pos, N-1, [BinTerm | Ack], Bad);
261	_ ->
262	    BytesToRead = Size + ?HEADERSZ,
263            {#continuation{pos = Pos - byte_size(B), b = BytesToRead}, Ack, Bad}
264    end;
265handle_chunk_ro(B= <<Size:?SIZESZ/unit:8, ?BIGMAGICINT:?MAGICSZ/unit:8,
266                Tail/binary>>, Pos, N, Ack, Bad) -> % when Size>=?MIN_MD5_TERM
267    MD5 = erlang:md5(<<Size:?SIZESZ/unit:8>>),
268    case Tail of
269        <<MD5:16/binary, Bin:Size/binary>> ->
270            %% The requested object is always bigger than a chunk.
271            {#continuation{pos = Pos, b = []}, [Bin | Ack], Bad};
272        <<MD5:16/binary, _/binary>> ->
273            BytesToRead = Size + ?HEADERSZ + 16,
274            {#continuation{pos = Pos - byte_size(B), b = BytesToRead}, Ack, Bad};
275        <<_BadMD5:16/binary, _:1/unit:8, Tail2/binary>> ->
276            handle_chunk_ro(Tail2, Pos, N-1, Ack, Bad+1);
277        _ ->
278            {#continuation{pos = Pos - byte_size(B), b = []}, Ack, Bad}
279    end;
280handle_chunk_ro(B= <<Size:?SIZESZ/unit:8, ?MAGICINT:?MAGICSZ/unit:8,
281                Tail/binary>>, Pos, N, Ack, Bad) ->
282    %% Version 2, before 2(a).
283    case Tail of
284	<<BinTerm:Size/binary, Tail2/binary>> ->
285	    handle_chunk_ro(Tail2, Pos, N-1, [BinTerm | Ack], Bad);
286	_ ->
287	    %% We read the whole thing into one binary, even if Size is huge.
288	    BytesToRead = Size + ?HEADERSZ,
289            {#continuation{pos = Pos - byte_size(B), b = BytesToRead}, Ack, Bad}
290    end;
291handle_chunk_ro(B, Pos, N, Ack, Bad) when byte_size(B) >= ?HEADERSZ ->
292    <<_:1/unit:8, B2/binary>> = B,
293    handle_chunk_ro(B2, Pos, N-1, Ack, Bad+1);
294handle_chunk_ro(B, Pos, _N, Ack, Bad) ->
295    {#continuation{pos = Pos-byte_size(B), b = []}, Ack, Bad}.
296
297read_chunk_ro(FdC, FileName, Pos, MaxBytes) ->
298    pread(FdC, FileName, Pos + ?HEADSZ, MaxBytes).
299
300%% -> ok | throw(Error)
301close(#cache{fd = Fd, c = []}, FileName, read_only) ->
302    case file:close(Fd) of
303        ok -> ok;
304        Error -> file_error(FileName, Error)
305    end;
306close(#cache{fd = Fd, c = C}, FileName, read_write) ->
307    {Reply, _NewFdC} = write_cache(Fd, FileName, C),
308    mark(Fd, FileName, ?CLOSED),
309    case file:close(Fd) of
310        ok -> ok;
311        Error -> file_error(FileName, Error)
312    end,
313    if Reply =:= ok -> ok; true -> throw(Reply) end.
314
315%% Open an internal file. Head is ignored if Mode is read_only.
316%% int_open(FileName, Repair, Mode, Head) ->
317%%    {ok, {Alloc, FdC, HeadSize, FileSize}}
318%%  | {repaired, FdC, Terms, BadBytes, FileSize}
319%%  | throw(Error)
320%% Alloc = new | existed
321%% HeadSize = {NumberOfItemsWritten, NumberOfBytesWritten}
322%% (HeadSize is equal {0, 0} if Alloc =:= existed, or no header written.)
323int_open(FName, truncate, read_write, Head) ->
324    new_int_file(FName, Head);
325int_open(FName, Repair, read_write, Head) ->
326    case open_read(FName) of
327	{ok, Fd} ->  %% File exists
328	    case file:read(Fd, ?HEADSZ) of
329		{ok, FileHead} ->
330		    case is_head(FileHead) of
331			yes ->
332                            case file:close(Fd) of
333                                ok -> ok;
334                                Error2 -> file_error(FName, Error2)
335                            end,
336			    case open_update(FName) of
337				{ok, Fd2} ->
338				    mark(Fd2, FName, ?OPENED),
339                                    FdC1 = #cache{fd = Fd2},
340				    {FdC, P} = position_close(FdC1, FName,eof),
341				    {ok, {existed, FdC, {0, 0}, P}};
342				Error ->
343				    file_error(FName, Error)
344			    end;
345			yes_not_closed when Repair ->
346			    repair(Fd, FName);
347			yes_not_closed when not Repair ->
348			    _ = file:close(Fd),
349			    throw({error, {need_repair, FName}});
350			no ->
351			    _ = file:close(Fd),
352			    throw({error, {not_a_log_file, FName}})
353		    end;
354		eof ->
355		    _= file:close(Fd),
356		    throw({error, {not_a_log_file, FName}});
357		Error ->
358		    file_error_close(Fd, FName, Error)
359	    end;
360	_Other ->
361	    new_int_file(FName, Head)
362    end;
363int_open(FName, _Repair, read_only, _Head) ->
364    case open_read(FName) of
365	{ok, Fd} ->  %% File exists
366	    case file:read(Fd, ?HEADSZ) of
367		{ok, Head} ->
368		    case is_head(Head) of
369			yes ->
370			    {ok, P} = position_close2(Fd, FName, eof),
371                            FdC = #cache{fd = Fd},
372			    {ok, {existed, FdC, {0, 0}, P}};
373			yes_not_closed  ->
374			    {ok, P} = position_close2(Fd, FName, eof),
375                            FdC = #cache{fd = Fd},
376			    {ok, {existed, FdC, {0, 0}, P}};
377			no ->
378			    _= file:close(Fd),
379			    throw({error, {not_a_log_file, FName}})
380		    end;
381		eof ->
382		    _ = file:close(Fd),
383		    throw({error, {not_a_log_file, FName}});
384		Error ->
385		    file_error_close(Fd, FName, Error)
386	    end;
387	Error ->
388	    file_error(FName, Error)
389    end.
390
391new_int_file(FName, Head) ->
392    case open_update(FName) of
393	{ok, Fd} ->
394            ok = truncate_at_close2(Fd, FName, bof),
395            fwrite_close2(Fd, FName, [?LOGMAGIC, ?OPENED]),
396            {FdC1, Nh, HeadSz} = int_log_head(Fd, Head),
397	    {FdC, FileSize} = position_close(FdC1, FName, cur),
398            {ok, {new, FdC, {Nh, ?HEADERSZ + HeadSz}, FileSize}};
399	Error ->
400	    file_error(FName, Error)
401    end.
402
403%% -> {FdC, NoItemsWritten, NoBytesWritten} | throw(Error)
404int_log_head(Fd, Head) ->
405    case lh(Head, internal) of
406	{ok, BinHead} ->
407            {Bs, Size} = logl([BinHead]),
408            {ok, FdC} = fwrite_header(Fd, Bs, Size),
409            {FdC, 1, Size};
410	none ->
411	    {#cache{fd = Fd}, 0, 0};
412	Error ->
413	    _= file:close(Fd),
414	    throw(Error)
415    end.
416
417%% Open an external file.
418%% -> {ok, {Alloc, FdC, HeadSize}, FileSize} | throw(Error)
419ext_open(FName, truncate, read_write, Head) ->
420    new_ext_file(FName, Head);
421ext_open(FName, _Repair, read_write, Head) ->
422    case file:read_file_info(FName) of
423	{ok, _FileInfo} ->
424	    case open_update(FName) of
425		{ok, Fd} ->
426		    {ok, P} = position_close2(Fd, FName, eof),
427                    FdC = #cache{fd = Fd},
428		    {ok, {existed, FdC, {0, 0}, P}};
429		Error ->
430		    file_error(FName, Error)
431	    end;
432	_Other ->
433	    new_ext_file(FName, Head)
434    end;
435ext_open(FName, _Repair, read_only, _Head) ->
436    case open_read(FName) of
437	{ok, Fd} ->
438	    {ok, P} = position_close2(Fd, FName, eof),
439            FdC = #cache{fd = Fd},
440	    {ok, {existed, FdC, {0, 0}, P}};
441	Error ->
442	    file_error(FName, Error)
443    end.
444
445new_ext_file(FName, Head) ->
446    case open_truncate(FName) of
447	{ok, Fd} ->
448	    {FdC1, HeadSize} = ext_log_head(Fd, Head),
449	    {FdC, FileSize} = position_close(FdC1, FName, cur),
450	    {ok, {new, FdC, HeadSize, FileSize}};
451	Error ->
452	    file_error(FName, Error)
453    end.
454
455%% -> {FdC, {NoItemsWritten, NoBytesWritten}} | throw(Error)
456ext_log_head(Fd, Head) ->
457    case lh(Head, external) of
458	{ok, BinHead} ->
459            Size = byte_size(BinHead),
460            {ok, FdC} = fwrite_header(Fd, BinHead, Size),
461            {FdC, {1, Size}};
462	none ->
463	    {#cache{fd = Fd}, {0, 0}};
464	Error ->
465            _= file:close(Fd),
466	    throw(Error)
467    end.
468
469%% -> _Any | throw()
470mark(Fd, FileName, What) ->
471    {ok, _} = position_close2(Fd, FileName, 4),
472    fwrite_close2(Fd, FileName, What).
473
474%% -> {ok, Bin} | Error
475lh({ok, Bin}, _Format) ->
476    {ok, Bin};
477lh({M, F, A}, Format) when is_list(A) ->
478    case catch apply(M, F, A) of
479	{ok, Head} when Format =:= internal ->
480	    {ok, term_to_binary(Head)};
481	{ok, Bin} when is_binary(Bin) ->
482	    {ok, Bin};
483	{ok, Bytes} ->
484	    case catch list_to_binary(Bytes) of
485		{'EXIT', _} ->
486		    {error, {invalid_header, {{M,F,A}, {ok, Bytes}}}};
487		Bin ->
488		    {ok, Bin}
489	    end;
490	{'EXIT', Error} ->
491	    {error, {invalid_header, {{M,F,A}, Error}}};
492	Error ->
493	    {error, {invalid_header, {{M,F,A}, Error}}}
494    end;
495lh({M, F, A}, _Format) -> % cannot happen
496    {error, {invalid_header, {M, F, A}}};
497lh(none, _Format) ->
498    none;
499lh(H, _F) -> % cannot happen
500    {error, {invalid_header, H}}.
501
502repair(In, File) ->
503    FSz = file_size(File),
504    case is_quiet() of
505        true -> ok;
506        _ -> error_logger:info_msg("disk_log: repairing ~tp ...\n", [File])
507    end,
508    Tmp = add_ext(File, "TMP"),
509    {ok, {_Alloc, Out, {0, _}, _FileSize}} = new_int_file(Tmp, none),
510    scan_f_read(<<>>, In, Out, File, FSz, Tmp, ?MAX_CHUNK_SIZE, 0, 0).
511
512scan_f_read(B, In, Out, File, FSz, Tmp, MaxBytes, No, Bad) ->
513    case file:read(In, MaxBytes) of
514        eof ->
515            done_scan(In, Out, Tmp, File, No, Bad+byte_size(B));
516        {ok, Bin}  ->
517            NewBin = list_to_binary([B, Bin]),
518            {NB, NMax, Ack, NNo, NBad} =
519                scan_f(NewBin, FSz, [], No, Bad),
520            case log(Out, Tmp, lists:reverse(Ack)) of
521                {ok, _Size, NewOut} ->
522                    scan_f_read(NB, In, NewOut, File, FSz, Tmp, NMax,NNo,NBad);
523                {{error, {file_error, _Filename, Error}}, NewOut} ->
524                    repair_err(In, NewOut, Tmp, File, {error, Error})
525            end;
526        Error ->
527            repair_err(In, Out, Tmp, File, Error)
528    end.
529
530scan_f(B = <<Size:?SIZESZ/unit:8, ?BIGMAGICINT:?MAGICSZ/unit:8, Tail/binary>>,
531       FSz, Ack, No, Bad) when Size < ?MIN_MD5_TERM ->
532    scan_f2(B, FSz, Ack, No, Bad, Size, Tail);
533scan_f(B = <<Size:?SIZESZ/unit:8, ?BIGMAGICINT:?MAGICSZ/unit:8, Tail/binary>>,
534       FSz, Ack, No, Bad) -> % when Size >= ?MIN_MD5_TERM
535    MD5 = erlang:md5(<<Size:?SIZESZ/unit:8>>),
536    case Tail of
537        <<MD5:16/binary, BinTerm:Size/binary, Tail2/binary>> ->
538            case catch binary_to_term(BinTerm) of
539                {'EXIT', _} ->
540                    scan_f(Tail2, FSz, Ack, No, Bad+Size);
541                _Term ->
542                    scan_f(Tail2, FSz, [BinTerm | Ack], No+1, Bad)
543            end;
544        <<MD5:16/binary, _/binary>> ->
545            {B, Size-byte_size(Tail)+16, Ack, No, Bad};
546        _ when byte_size(Tail) < 16 ->
547            {B, Size-byte_size(Tail)+16, Ack, No, Bad};
548        _ ->
549            <<_:8, B2/binary>> = B,
550            scan_f(B2, FSz, Ack, No, Bad+1)
551    end;
552scan_f(B = <<Size:?SIZESZ/unit:8, ?MAGICINT:?MAGICSZ/unit:8, Tail/binary>>,
553       FSz, Ack, No, Bad) when Size =< FSz ->
554    %% Since the file is not compressed, the item size cannot exceed
555    %% the file size.
556    scan_f2(B, FSz, Ack, No, Bad, Size, Tail);
557scan_f(B = <<_:?HEADERSZ/unit:8, _/binary>>, FSz, Ack, No, Bad) ->
558    <<_:8, B2/binary>> = B,
559    scan_f(B2, FSz, Ack, No, Bad + 1);
560scan_f(B, _FSz, Ack, No, Bad) ->
561    {B, ?MAX_CHUNK_SIZE, Ack, No, Bad}.
562
563scan_f2(B, FSz, Ack, No, Bad, Size, Tail) ->
564    case Tail of
565        <<BinTerm:Size/binary, Tail2/binary>> ->
566            case catch binary_to_term(BinTerm) of
567                {'EXIT', _} ->
568                    <<_:8, B2/binary>> = B,
569                    scan_f(B2, FSz, Ack, No, Bad+1);
570                _Term ->
571                    scan_f(Tail2, FSz, [BinTerm | Ack], No+1, Bad)
572            end;
573        _ ->
574            {B, Size-byte_size(Tail), Ack, No, Bad}
575    end.
576
577done_scan(In, Out, OutName, FName, RecoveredTerms, BadChars) ->
578    _ = file:close(In),
579    case catch fclose(Out, OutName) of
580        ok ->
581            case file:rename(OutName, FName) of
582                ok ->
583                    case open_update(FName) of
584                        {ok, New} ->
585                            {ok, P} = position_close2(New, FName, eof),
586                            FdC = #cache{fd = New},
587                            {repaired, FdC, RecoveredTerms, BadChars, P};
588                        Error ->
589                            file_error(FName, Error)
590                    end;
591                Error ->
592                    _ = file:delete(OutName),
593                    file_error(FName, Error)
594            end;
595        Error ->
596            _ = file:delete(OutName),
597            throw(Error)
598    end.
599
600-spec repair_err(file:io_device(), #cache{}, file:filename(),
601		 file:filename(), {'error', file:posix()}) -> no_return().
602repair_err(In, Out, OutName, ErrFileName, Error) ->
603    _= file:close(In),
604    catch fclose(Out, OutName),
605    %% OutName is often the culprit, try to remove it anyway...
606    _ = file:delete(OutName),
607    file_error(ErrFileName, Error).
608
609%% Used by wrap_log_reader.
610-spec is_head(binary()) -> 'yes' | 'yes_not_closed' | 'no'.
611is_head(<<M:4/binary, S:4/binary>>) when ?LOGMAGIC =:= M, ?CLOSED =:= S ->
612    yes;
613is_head(<<M:4/binary, S:4/binary>>) when ?LOGMAGIC =:= M, ?OPENED =:= S ->
614    yes_not_closed;
615is_head(Bin) when is_binary(Bin) ->
616    no.
617
618%%-----------------------------------------------------------------
619%% Func: mf_int_open/7, mf_ext_open/7
620%% Args: FName = file:filename()
621%%       MaxB = integer()
622%%       MaxF = integer()
623%%       Repair = truncate | true | false
624%%       Mode = read_write | read_only
625%%       Head = none | {ok, Bin} | {M, F, A}
626%%       Version = integer()
627%% Purpose: An ADT for wrapping logs.  mf_int_ writes binaries (mf_ext_
628%%          writes bytes)
629%%          to files called FName.1, FName.2, ..., FName.MaxF.
630%%          Writes MaxB bytes on each file.
631%%          Creates a file called Name.idx in the Dir.  This
632%%          file contains the last written FileName as one byte, and
633%%          following that, the sizes of each file (size 0 number of items).
634%%          On startup, this file is read, and the next available
635%%          filename is used as first log file.
636%%          Reports can be browsed with Report Browser Tool (rb), or
637%%          read with disk_log.
638%%-----------------------------------------------------------------
639-spec mf_int_open(FName   :: file:filename(),
640		  MaxB    :: integer(),
641		  MaxF    :: integer(),
642		  Repair  :: dlog_repair(),
643		  Mode    :: dlog_mode(),
644		  Head    :: dlog_head(),
645		  Version :: integer())
646      -> {'ok', #handle{}, integer()}
647       | {'repaired', #handle{},
648	  non_neg_integer(), non_neg_integer(), non_neg_integer()}.
649%%     | throw(FileError)
650mf_int_open(FName, MaxB, MaxF, Repair, Mode, Head, Version) ->
651    {First, Sz, TotSz, NFiles} = read_index_file(Repair, FName, MaxF),
652    write_size_file(Mode, FName, MaxB, MaxF, Version),
653    NewMaxF = if
654		  NFiles > MaxF ->
655		      {MaxF, NFiles};
656		  true ->
657		      MaxF
658	      end,
659    case int_file_open(FName, First, 0, 0, Head, Repair, Mode) of
660	{ok, FdC, FileName, Lost, {NoItems, NoBytes}, FSz} ->
661	    % firstPos = NoBytes is not always correct when the file
662	    % existed, but it will have to do since we don't know
663	    % where the header ends.
664	    CurCnt = Sz + NoItems - Lost,
665	    {ok, #handle{filename = FName, maxB = MaxB,
666			 maxF = NewMaxF, curF = First, cur_fdc = FdC,
667			 cur_name = FileName, cur_cnt = CurCnt,
668			 acc_cnt = -Sz, curB = FSz,
669			 firstPos = NoBytes, noFull = 0, accFull = 0},
670	     TotSz + CurCnt};
671	{repaired, FdC, FileName, Rec, Bad, FSz} ->
672	    {repaired,
673	     #handle{filename = FName, maxB = MaxB, cur_name = FileName,
674		     maxF = NewMaxF, curF = First, cur_fdc = FdC,
675		     cur_cnt = Rec, acc_cnt = -Rec, curB = FSz,
676		     firstPos = 0, noFull = 0, accFull = 0},
677	     Rec, Bad, TotSz + Rec}
678    end.
679
680%% -> {ok, handle(), Lost} | {error, Error, handle()}
681mf_int_inc(Handle, Head) ->
682    #handle{filename = FName, cur_cnt = CurCnt, acc_cnt = AccCnt,
683	    cur_name = FileName, curF = CurF, maxF = MaxF,
684	    cur_fdc = CurFdC, noFull = NoFull} = Handle,
685    case catch wrap_int_log(FName, CurF, MaxF, CurCnt, Head) of
686	{NewF, NewMaxF, NewFdC, NewFileName, Nh, FirstPos, Lost} ->
687	    Handle1 = Handle#handle{cur_fdc = NewFdC, curF = NewF,
688				    cur_name = NewFileName,
689				    cur_cnt = Nh, acc_cnt = AccCnt + CurCnt,
690				    maxF = NewMaxF, firstPos = FirstPos,
691				    curB = FirstPos, noFull = NoFull + 1},
692	    case catch close(CurFdC, FileName, read_write) of
693		ok ->
694		    {ok, Handle1, Lost};
695		Error -> % Error in the last file, new file opened.
696		    {error, Error, Handle1}
697	    end;
698	Error ->
699	    {error, Error, Handle}
700    end.
701
702%% -> {ok, handle(), Logged, Lost, NoWraps} | {ok, handle(), Logged}
703%%    | {error, Error, handle(), Logged, Lost}
704%% The returned handle is not always valid - something may
705%% have been written before things went wrong.
706mf_int_log(Handle, Bins, Head) ->
707    mf_int_log(Handle, Bins, Head, 0, []).
708
709mf_int_log(Handle, [], _Head, No, []) ->
710    {ok, Handle, No};
711mf_int_log(Handle, [], _Head, No, Wraps0) ->
712    Wraps = reverse(Wraps0),
713    {ok, Handle, No, sum(Wraps), Wraps};
714mf_int_log(Handle, Bins, Head, No0, Wraps) ->
715    #handle{curB = CurB, maxB = MaxB, cur_name = FileName, cur_fdc = CurFdC,
716            firstPos = FirstPos0, cur_cnt = CurCnt} = Handle,
717    {FirstBins, LastBins, NoBytes, N} =
718	int_split_bins(CurB, MaxB, FirstPos0, Bins),
719    case FirstBins of
720	[] ->
721            #handle{filename = FName, curF = CurF, maxF = MaxF,
722                    acc_cnt = AccCnt, noFull = NoFull} = Handle,
723	    case catch wrap_int_log(FName, CurF, MaxF, CurCnt, Head) of
724		{NewF, NewMaxF, NewFdC, NewFileName, Nh, FirstPos, Lost} ->
725		    Handle1 = Handle#handle{cur_fdc = NewFdC, curF = NewF,
726					    cur_cnt = Nh,
727					    cur_name = NewFileName,
728					    acc_cnt = AccCnt + CurCnt,
729					    maxF = NewMaxF,
730					    curB = FirstPos,
731					    firstPos = FirstPos,
732					    noFull = NoFull + 1},
733		    case catch close(CurFdC, FileName, read_write) of
734			ok ->
735			    mf_int_log(Handle1, Bins, Head, No0 + Nh,
736				       [Lost | Wraps]);
737			Error ->
738			    Lost1 = Lost + sum(Wraps),
739			    {error, Error, Handle1, No0 + Nh, Lost1}
740		    end;
741		Error ->
742		    {error, Error, Handle, No0, sum(Wraps)}
743	    end;
744	_ ->
745	    case fwrite(CurFdC, FileName, FirstBins, NoBytes) of
746                {ok, NewCurFdC} ->
747		    Handle1 = Handle#handle{cur_fdc = NewCurFdC,
748                                            curB = CurB + NoBytes,
749					    cur_cnt = CurCnt + N},
750		    mf_int_log(Handle1, LastBins, Head, No0 + N, Wraps);
751		{Error, NewCurFdC} ->
752		    Handle1 = Handle#handle{cur_fdc = NewCurFdC},
753		    {error, Error, Handle1, No0, sum(Wraps)}
754	    end
755    end.
756
757wrap_int_log(FName, CurF, MaxF, CurCnt, Head) ->
758    {NewF, NewMaxF} = inc_wrap(FName, CurF, MaxF),
759    {ok, NewFdC, NewFileName, Lost, {Nh, FirstPos}, _FileSize} =
760	int_file_open(FName, NewF, CurF, CurCnt, Head),
761    {NewF, NewMaxF, NewFdC, NewFileName, Nh, FirstPos, Lost}.
762
763%% -> {NewHandle, Reply}, Reply = {Cont, Binaries} | {error, Reason} | eof
764mf_int_chunk(Handle, 0, Bin, N) ->
765    FirstF = find_first_file(Handle),
766    mf_int_chunk(Handle, {FirstF, 0}, Bin, N);
767mf_int_chunk(#handle{curF = FileNo, cur_fdc = FdC, cur_name = FileName}
768             = Handle, {FileNo, Pos}, Bin, N) ->
769    {NewFdC, Reply} = chunk(FdC, FileName, Pos, Bin, N),
770    {Handle#handle{cur_fdc = NewFdC}, conv(Reply, FileNo)};
771mf_int_chunk(Handle, {FileNo, Pos}, Bin, N) ->
772    FName = add_ext(Handle#handle.filename, FileNo),
773    NFileNo = inc(FileNo, Handle#handle.maxF),
774    case catch int_open(FName, true, read_only, any) of
775	{error, _Reason} ->
776	    case is_quiet() of
777		true -> ok;
778		_ -> error_logger:info_msg("disk_log: chunk error. File ~tp missing.\n\n",
779					   [FName])
780	    end,
781	    mf_int_chunk(Handle, {NFileNo, 0}, [], N);
782	{ok, {_Alloc, FdC, _HeadSize, _FileSize}} ->
783	    case chunk(FdC, FName, Pos, Bin, N) of
784		{NewFdC, eof} ->
785		    _ = file:close(NewFdC#cache.fd),
786		    mf_int_chunk(Handle, {NFileNo, 0}, [], N);
787		{NewFdC, Other} ->
788		    _ = file:close(NewFdC#cache.fd),
789		    {Handle, conv(Other, FileNo)}
790	    end
791    end.
792
793%% -> {NewHandle, Reply},
794%%    Reply = {Cont, Binaries, Bad} (Bad >= 0) | {error, Reason} | eof
795mf_int_chunk_read_only(Handle, 0, Bin, N) ->
796    FirstF = find_first_file(Handle),
797    mf_int_chunk_read_only(Handle, {FirstF, 0}, Bin, N);
798mf_int_chunk_read_only(#handle{curF = FileNo, cur_fdc = FdC, cur_name=FileName}
799                       = Handle, {FileNo, Pos}, Bin, N) ->
800    {NewFdC, Reply} = do_chunk_read_only(FdC, FileName, Pos, Bin, N),
801    {Handle#handle{cur_fdc = NewFdC}, conv(Reply, FileNo)};
802mf_int_chunk_read_only(Handle, {FileNo, Pos}, Bin, N) ->
803    FName = add_ext(Handle#handle.filename, FileNo),
804    NFileNo = inc(FileNo, Handle#handle.maxF),
805    case catch int_open(FName, true, read_only, any) of
806	{error, _Reason} ->
807	    case is_quiet() of
808		true -> ok;
809		_ -> error_logger:info_msg("disk_log: chunk error. File ~tp missing.\n\n",
810					   [FName])
811	    end,
812	    mf_int_chunk_read_only(Handle, {NFileNo, 0}, [], N);
813	{ok, {_Alloc, FdC, _HeadSize, _FileSize}} ->
814	    case do_chunk_read_only(FdC, FName, Pos, Bin, N) of
815		{NewFdC, eof} ->
816		    _ = file:close(NewFdC#cache.fd),
817		    mf_int_chunk_read_only(Handle, {NFileNo,0}, [], N);
818		{NewFdC, Other} ->
819		    _ = file:close(NewFdC#cache.fd),
820		    {Handle, conv(Other, FileNo)}
821	    end
822    end.
823
824%% -> {ok, Cont} | Error
825mf_int_chunk_step(Handle, 0, Step) ->
826    FirstF = find_first_file(Handle),
827    mf_int_chunk_step(Handle, {FirstF, 0}, Step);
828mf_int_chunk_step(Handle, {FileNo, _Pos}, Step) ->
829    NFileNo = inc(FileNo, Handle#handle.maxF, Step),
830    FileName = add_ext(Handle#handle.filename, NFileNo),
831    case file:read_file_info(FileName) of
832	{ok, _FileInfo} ->
833	    {ok, #continuation{pos = {NFileNo, 0}, b = []}};
834	_Error ->
835	    {error, end_of_log}
836    end.
837
838%% -> {Reply, handle()}; Reply = ok | Error
839mf_write_cache(#handle{filename = FName, cur_fdc = FdC} = Handle) ->
840    erase(write_cache_timer_is_running),
841    #cache{fd = Fd, c = C} = FdC,
842    {Reply, NewFdC} = write_cache(Fd, FName, C),
843    {Reply, Handle#handle{cur_fdc = NewFdC}}.
844
845%% -> {Reply, handle()}; Reply = ok | Error
846mf_sync(#handle{filename = FName, cur_fdc = FdC} = Handle) ->
847    {Reply, NewFdC} = fsync(FdC, FName),
848    {Reply, Handle#handle{cur_fdc = NewFdC}}.
849
850%% -> ok | throw(FileError)
851mf_int_close(#handle{filename = FName, curF = CurF, cur_name = FileName,
852		     cur_fdc = CurFdC, cur_cnt = CurCnt}, Mode) ->
853    close(CurFdC, FileName, Mode),
854    write_index_file(Mode, FName, CurF, CurF, CurCnt),
855    ok.
856
857%% -> {ok, handle(), Cnt} | throw(FileError)
858mf_ext_open(FName, MaxB, MaxF, Repair, Mode, Head, Version) ->
859    {First, Sz, TotSz, NFiles} = read_index_file(Repair, FName, MaxF),
860    write_size_file(Mode, FName, MaxB, MaxF, Version),
861    NewMaxF = if
862		  NFiles > MaxF ->
863		      {MaxF, NFiles};
864		  true ->
865		      MaxF
866	      end,
867    {ok, FdC, FileName, Lost, {NoItems, NoBytes}, CurB} =
868	ext_file_open(FName, First, 0, 0, Head, Repair, Mode),
869    CurCnt = Sz + NoItems - Lost,
870    {ok, #handle{filename = FName, maxB = MaxB, cur_name = FileName,
871		 maxF = NewMaxF, cur_cnt = CurCnt, acc_cnt = -Sz,
872		 curF = First, cur_fdc = FdC, firstPos = NoBytes,
873		 curB = CurB, noFull = 0, accFull = 0},
874     TotSz + CurCnt}.
875
876%% -> {ok, handle(), Lost}
877%%   | {error, Error, handle()}
878%%   | throw(FatalError)
879%% Fatal errors should always terminate the log.
880mf_ext_inc(Handle, Head) ->
881    #handle{filename = FName, cur_cnt = CurCnt, cur_name = FileName,
882	    acc_cnt = AccCnt, curF = CurF, maxF = MaxF, cur_fdc = CurFdC,
883	    noFull = NoFull} = Handle,
884    case catch wrap_ext_log(FName, CurF, MaxF, CurCnt, Head) of
885	{NewF, NewMaxF, NewFdC, NewFileName, Nh, FirstPos, Lost} ->
886	    Handle1 = Handle#handle{cur_fdc = NewFdC, curF = NewF,
887				    cur_name = NewFileName,
888				    cur_cnt = Nh, acc_cnt = AccCnt + CurCnt,
889				    maxF = NewMaxF, firstPos = FirstPos,
890				    curB = FirstPos, noFull = NoFull + 1},
891	    case catch fclose(CurFdC, FileName) of
892		ok ->
893		    {ok, Handle1, Lost};
894		Error -> % Error in the last file, new file opened.
895		    {error, Error, Handle1}
896	    end;
897	Error ->
898	    {error, Error, Handle}
899    end.
900
901%% -> {ok, handle(), Logged, Lost, NoWraps} | {ok, handle(), Logged}
902%%    | {error, Error, handle(), Logged, Lost}
903
904%% The returned handle is not always valid -
905%% something may have been written before things went wrong.
906mf_ext_log(Handle, Bins, Head) ->
907    mf_ext_log(Handle, Bins, Head, 0, []).
908
909mf_ext_log(Handle, [], _Head, No, []) ->
910    {ok, Handle, No};
911mf_ext_log(Handle, [], _Head, No, Wraps0) ->
912    Wraps = reverse(Wraps0),
913    {ok, Handle, No, sum(Wraps), Wraps};
914mf_ext_log(Handle, Bins, Head, No0, Wraps) ->
915    #handle{curB = CurB, maxB = MaxB, cur_name = FileName, cur_fdc = CurFdC,
916            firstPos = FirstPos0, cur_cnt = CurCnt} = Handle,
917    {FirstBins, LastBins, NoBytes, N} =
918	ext_split_bins(CurB, MaxB, FirstPos0, Bins),
919    case FirstBins of
920	[] ->
921            #handle{filename = FName, curF = CurF, maxF = MaxF,
922                    acc_cnt = AccCnt, noFull = NoFull} = Handle,
923	    case catch wrap_ext_log(FName, CurF, MaxF, CurCnt, Head) of
924		{NewF, NewMaxF, NewFdC, NewFileName, Nh, FirstPos, Lost} ->
925		    Handle1 = Handle#handle{cur_fdc = NewFdC, curF = NewF,
926					    cur_cnt = Nh,
927					    cur_name = NewFileName,
928					    acc_cnt = AccCnt + CurCnt,
929					    maxF = NewMaxF,
930					    curB = FirstPos,
931					    firstPos = FirstPos,
932					    noFull = NoFull + 1},
933		    case catch fclose(CurFdC, FileName) of
934			ok ->
935			    mf_ext_log(Handle1, Bins, Head, No0 + Nh,
936				       [Lost | Wraps]);
937			Error ->
938			    Lost1 = Lost + sum(Wraps),
939			    {error, Error, Handle1, No0 + Nh, Lost1}
940		    end;
941		Error ->
942		    {error, Error, Handle, No0, sum(Wraps)}
943	    end;
944	_ ->
945	    case fwrite(CurFdC, FileName, FirstBins, NoBytes) of
946                {ok, NewCurFdC} ->
947		    Handle1 = Handle#handle{cur_fdc = NewCurFdC,
948                                            curB = CurB + NoBytes,
949					    cur_cnt = CurCnt + N},
950		    mf_ext_log(Handle1, LastBins, Head, No0 + N, Wraps);
951		{Error, NewCurFdC} ->
952		    Handle1 = Handle#handle{cur_fdc = NewCurFdC},
953		    {error, Error, Handle1, No0, sum(Wraps)}
954	    end
955    end.
956
957wrap_ext_log(FName, CurF, MaxF, CurCnt, Head) ->
958    {NewF, NewMaxF} = inc_wrap(FName, CurF, MaxF),
959    {ok, NewFdC, NewFileName, Lost, {Nh, FirstPos}, _FileSize} =
960	ext_file_open(FName, NewF, CurF, CurCnt, Head),
961    {NewF, NewMaxF, NewFdC, NewFileName, Nh, FirstPos, Lost}.
962
963%% -> ok | throw(FileError)
964mf_ext_close(#handle{filename = FName, curF = CurF,
965		     cur_fdc = CurFdC, cur_cnt = CurCnt}, Mode) ->
966    Res = (catch fclose(CurFdC, FName)),
967    write_index_file(Mode, FName, CurF, CurF, CurCnt),
968    Res.
969
970%% -> {ok, handle()} | throw(FileError)
971change_size_wrap(Handle, {NewMaxB, NewMaxF}, Version) ->
972    FName = Handle#handle.filename,
973    {_MaxB, MaxF} = get_wrap_size(Handle),
974    write_size_file(read_write, FName, NewMaxB, NewMaxF, Version),
975    if
976	NewMaxF > MaxF ->
977	    remove_files(FName, MaxF + 1, NewMaxF),
978	    {ok, Handle#handle{maxB = NewMaxB, maxF = NewMaxF}};
979	NewMaxF < MaxF ->
980	    {ok, Handle#handle{maxB = NewMaxB, maxF = {NewMaxF, MaxF}}};
981	true ->
982	    {ok, Handle#handle{maxB = NewMaxB, maxF = NewMaxF}}
983    end.
984
985%%-----------------------------------------------------------------
986%% Misc functions
987%%-----------------------------------------------------------------
988%% -> {ok, FdC, FileName, Lost, HeadSize, FileSize} | throw(Error)
989int_file_open(FName, NewFile, OldFile, OldCnt, Head) ->
990    Repair = truncate, Mode = read_write,
991    int_file_open(FName, NewFile, OldFile, OldCnt, Head, Repair, Mode).
992
993%% -> {ok, FdC, FileName, Lost, HeadSize, FileSize}
994%%  | {repaired, FdC, FileName, Rec, Bad, FileSize}
995%%  | throw(Error)
996int_file_open(FName, NewFile, OldFile, OldCnt, Head, Repair, Mode) ->
997    N = add_ext(FName, NewFile),
998    case int_open(N, Repair, Mode, Head) of
999	{ok, {_Alloc, FdC, HeadSize, FileSize}} ->
1000	    Lost = write_index_file(Mode, FName, NewFile, OldFile, OldCnt),
1001	    {ok, FdC, N, Lost, HeadSize, FileSize};
1002	{repaired, FdC, Recovered, BadBytes, FileSize} ->
1003	    write_index_file(Mode, FName, NewFile, OldFile, OldCnt),
1004	    {repaired, FdC, N, Recovered, BadBytes, FileSize}
1005    end.
1006
1007%% -> {ok, FdC, FileName, Lost, HeadSize, FileSize} | throw(Error)
1008ext_file_open(FName, NewFile, OldFile, OldCnt, Head) ->
1009    Repair = truncate, Mode = read_write,
1010    ext_file_open(FName, NewFile, OldFile, OldCnt, Head, Repair, Mode).
1011
1012ext_file_open(FName, NewFile, OldFile, OldCnt, Head, Repair, Mode) ->
1013    FileName = add_ext(FName, NewFile),
1014    {ok, {_Alloc, FdC, HeadSize, FileSize}} =
1015        ext_open(FileName, Repair, Mode, Head),
1016    Lost = write_index_file(Mode, FName, NewFile, OldFile, OldCnt),
1017    {ok, FdC, FileName, Lost, HeadSize, FileSize}.
1018
1019%%-----------------------------------------------------------------
1020%% The old file format for index file (CurFileNo > 0), Version 0:
1021%%
1022%% CurFileNo SizeFile1 SizeFile2  ... SizeFileN
1023%%   1 byte   4 bytes    4 bytes       4 bytes
1024%%
1025%% The new file format for index file (NewFormat = 0), version 1:
1026%%
1027%% NewFormat CurFileNo SizeFile1 SizeFile2  ... SizeFileN
1028%%   1 byte   4 bytes    4 bytes       4 bytes
1029%%
1030%% The current file format for index file (sizes in bytes), version 2:
1031%%
1032%% 0 (1) 0 (4) FileFormatVersion (1) CurFileNo (4) SizeFile1 (8) ...
1033%%
1034%% (SizeFileI refers to number of items on the log file.)
1035%%-----------------------------------------------------------------
1036
1037-define(index_file_name(F), add_ext(F, "idx")).
1038
1039read_index_file(truncate, FName, MaxF) ->
1040    remove_files(FName, 2, MaxF),
1041    _ = file:delete(?index_file_name(FName)),
1042    {1, 0, 0, 0};
1043read_index_file(_, FName, _MaxF) ->
1044    read_index_file(FName).
1045
1046%% Used by wrap_log_reader.
1047%% -> {CurFileNo, CurFileSz, TotSz, NoFiles} | throw(FileError)
1048%%  where TotSz does not include CurFileSz.
1049
1050read_index_file(FName) ->
1051    FileName = ?index_file_name(FName),
1052    case open_read(FileName) of
1053	{ok, Fd} ->
1054	    R = case file:read(Fd, ?MAX_CHUNK_SIZE) of
1055		    {ok, <<0, 0:32, Version, CurF:32, Tail/binary>>}
1056		             when Version =:= ?VERSION,
1057				  0 < CurF, CurF < ?MAX_FILES ->
1058			parse_index(CurF, Version, 1, Tail, Fd, 0, 0, 0);
1059		    {ok, <<0, CurF:32, Tail/binary>>}
1060		             when 0 < CurF, CurF < ?MAX_FILES ->
1061			parse_index(CurF, 1, 1, Tail, Fd, 0, 0, 0);
1062		    {ok, <<CurF, Tail/binary>>} when 0 < CurF ->
1063			parse_index(CurF, 1, 1, Tail, Fd, 0, 0, 0);
1064		    _ErrorOrEof ->
1065			{1, 0, 0, 0}
1066		end,
1067	    _ = file:close(Fd),
1068	    R;
1069	_Error ->
1070	    {1, 0, 0, 0}
1071    end.
1072
1073parse_index(CurF, V, CurF, <<CurSz:64, Tail/binary>>, Fd, _, TotSz, NFiles)
1074          when V =:= ?VERSION ->
1075    parse_index(CurF, V, CurF+1, Tail, Fd, CurSz, TotSz, NFiles+1);
1076parse_index(CurF, V, N, <<Sz:64, Tail/binary>>, Fd, CurSz, TotSz, NFiles)
1077          when V =:= ?VERSION ->
1078    parse_index(CurF, V, N+1, Tail, Fd, CurSz, TotSz + Sz, NFiles+1);
1079parse_index(CurF, V, CurF, <<CurSz:32, Tail/binary>>, Fd, _, TotSz, NFiles)
1080          when V < ?VERSION ->
1081    parse_index(CurF, V, CurF+1, Tail, Fd, CurSz, TotSz, NFiles+1);
1082parse_index(CurF, V, N, <<Sz:32, Tail/binary>>, Fd, CurSz, TotSz, NFiles)
1083          when V < ?VERSION ->
1084    parse_index(CurF, V, N+1, Tail, Fd, CurSz, TotSz + Sz, NFiles+1);
1085parse_index(CurF, V, N, B, Fd, CurSz, TotSz, NFiles) ->
1086    case file:read(Fd, ?MAX_CHUNK_SIZE) of
1087	eof when 0 =:= byte_size(B) ->
1088	    {CurF, CurSz, TotSz, NFiles};
1089	{ok, Bin} ->
1090            NewB = list_to_binary([B, Bin]),
1091	    parse_index(CurF, V, N, NewB, Fd, CurSz, TotSz, NFiles);
1092	_ErrorOrEof ->
1093	    {1, 0, 0, 0}
1094    end.
1095
1096%% Returns: Number of lost items (if an old file was truncated)
1097%% -> integer() | throw(FileError)
1098write_index_file(read_only, _FName, _NewFile, _OldFile, _OldCnt) ->
1099    0;
1100write_index_file(read_write, FName, NewFile, OldFile, OldCnt) ->
1101    FileName = ?index_file_name(FName),
1102    case open_update(FileName) of
1103	{ok, Fd} ->
1104	    {Offset, SzSz} =
1105		case file:read(Fd, 6) of
1106		    eof ->
1107			Bin = <<0, 0:32, ?VERSION, NewFile:32>>,
1108			fwrite_close2(Fd, FileName, Bin),
1109			{10, 8};
1110		    {ok, <<0, 0:32, _Version>>} ->
1111			pwrite_close2(Fd, FileName, 6, <<NewFile:32>>),
1112			{10, 8};
1113		    {ok, <<0, _/binary>>} ->
1114			pwrite_close2(Fd, FileName, 1, <<NewFile:32>>),
1115			{5, 4};
1116		    {ok, <<_,_/binary>>} ->
1117                        %% Very old format, convert to the latest format!
1118			case file:read_file(FileName) of
1119			    {ok, <<_CurF, Tail/binary>>} ->
1120				{ok, _} = position_close2(Fd, FileName, bof),
1121				Bin = <<0, 0:32, ?VERSION, NewFile:32>>,
1122				NewTail = to_8_bytes(Tail, [], FileName, Fd),
1123				fwrite_close2(Fd, FileName, [Bin | NewTail]),
1124				{10, 8};
1125			    Error ->
1126				file_error_close(Fd, FileName, Error)
1127			end;
1128		    Error ->
1129			file_error_close(Fd, FileName, Error)
1130		end,
1131
1132	    NewPos = Offset + (NewFile - 1)*SzSz,
1133	    OldCntBin = <<OldCnt:SzSz/unit:8>>,
1134	    if
1135		OldFile > 0 ->
1136		    R = file:pread(Fd, NewPos, SzSz),
1137		    OldPos = Offset + (OldFile - 1)*SzSz,
1138		    pwrite_close2(Fd, FileName, OldPos, OldCntBin),
1139		    _ = file:close(Fd),
1140		    case R of
1141			{ok, <<Lost:SzSz/unit:8>>} -> Lost;
1142			{ok, _} ->
1143                            throw({error, {invalid_index_file, FileName}});
1144			eof    -> 0;
1145			Error2 -> file_error(FileName, Error2)
1146		    end;
1147		true ->
1148		    pwrite_close2(Fd, FileName, NewPos, OldCntBin),
1149		    _ = file:close(Fd),
1150		    0
1151	    end;
1152	E ->
1153	    file_error(FileName, E)
1154    end.
1155
1156-dialyzer({no_improper_lists, to_8_bytes/4}).
1157to_8_bytes(<<N:32,T/binary>>, NT, FileName, Fd) ->
1158    to_8_bytes(T, [NT | <<N:64>>], FileName, Fd);
1159to_8_bytes(B, NT, _FileName, _Fd) when byte_size(B) =:= 0 ->
1160    NT;
1161to_8_bytes(_B, _NT, FileName, Fd) ->
1162    _ = file:close(Fd),
1163    throw({error, {invalid_index_file, FileName}}).
1164
1165%% -> ok | throw(FileError)
1166index_file_trunc(FName, N) ->
1167    FileName = ?index_file_name(FName),
1168    case open_update(FileName) of
1169	{ok, Fd} ->
1170	    case file:read(Fd, 6) of
1171		eof ->
1172		    _ = file:close(Fd),
1173		    ok;
1174		{ok, <<0, 0:32, Version>>} when Version =:= ?VERSION ->
1175		    truncate_index_file(Fd, FileName, 10, 8, N);
1176		{ok, <<0, _/binary>>} ->
1177		    truncate_index_file(Fd, FileName, 5, 4, N);
1178		{ok, <<_, _/binary>>} -> % cannot happen
1179		    truncate_index_file(Fd, FileName, 1, 4, N);
1180		Error ->
1181		    file_error_close(Fd, FileName, Error)
1182	    end;
1183	Error ->
1184	    file_error(FileName, Error)
1185    end.
1186
1187truncate_index_file(Fd, FileName, Offset, N, SzSz) ->
1188    Pos = Offset + N*SzSz,
1189    case Pos > file_size(FileName) of
1190	true ->
1191	    ok = file:close(Fd);
1192	false ->
1193	    truncate_at_close2(Fd, FileName, {bof, Pos}),
1194	    ok = file:close(Fd)
1195    end,
1196    ok.
1197
1198print_index_file(File) ->
1199    io:format("-- Index begin --~n"),
1200    case file:read_file(File) of
1201	{ok, <<0, 0:32, Version, CurF:32, Tail/binary>>}
1202	         when Version =:= ?VERSION, 0 < CurF, CurF < ?MAX_FILES ->
1203	    io:format("cur file: ~w~n", [CurF]),
1204	    loop_index(1, Version, Tail);
1205	{ok, <<0, CurF:32, Tail/binary>>} when 0 < CurF, CurF < ?MAX_FILES ->
1206	    io:format("cur file: ~w~n", [CurF]),
1207	    loop_index(1, 1, Tail);
1208	{ok, <<CurF, Tail/binary>>} when 0 < CurF ->
1209	    io:format("cur file: ~w~n", [CurF]),
1210	    loop_index(1, 1, Tail);
1211	_Else ->
1212	    ok
1213    end,
1214    io:format("-- end --~n").
1215
1216loop_index(N, V, <<Sz:64, Tail/binary>>) when V =:= ?VERSION ->
1217    io:format(" ~p  items: ~w~n", [N, Sz]),
1218    loop_index(N+1, V, Tail);
1219loop_index(N, V, <<Sz:32, Tail/binary>>) when V < ?VERSION ->
1220    io:format(" ~p  items: ~w~n", [N, Sz]),
1221    loop_index(N+1, V, Tail);
1222loop_index(_, _, _) ->
1223    ok.
1224
1225-define(size_file_name(F), add_ext(F, "siz")).
1226
1227%% Version 0: no size file
1228%% Version 1: <<MaxSize:32, MaxFiles:32>>
1229%% Version 2: <<Version:8, MaxSize:64, MaxFiles:32>>
1230
1231%% -> ok | throw(FileError)
1232write_size_file(read_only, _FName, _NewSize, _NewMaxFiles, _Version) ->
1233    ok;
1234write_size_file(read_write, FName, NewSize, NewMaxFiles, Version) ->
1235    FileName = ?size_file_name(FName),
1236    Bin = if
1237	      Version =:=  ?VERSION ->
1238		  <<Version, NewSize:64, NewMaxFiles:32>>;
1239	      true ->
1240		  <<NewSize:32, NewMaxFiles:32>>
1241	  end,
1242    case file:write_file(FileName, Bin) of
1243	ok ->
1244	    ok;
1245	E ->
1246	    file_error(FileName, E)
1247    end.
1248
1249%% -> {NoBytes, NoFiles}.
1250read_size_file(FName) ->
1251    {Size,_Version} = read_size_file_version(FName),
1252    Size.
1253
1254%% -> {{NoBytes, NoFiles}, Version}, Version = integer() | undefined
1255read_size_file_version(FName) ->
1256    case file:read_file(?size_file_name(FName)) of
1257	{ok, <<Version, Size:64, MaxFiles:32>>} when Version =:= ?VERSION ->
1258	    {{Size, MaxFiles}, Version};
1259	{ok, <<Size:32, MaxFiles:32>>} ->
1260	    {{Size, MaxFiles}, 1};
1261	_ ->
1262	    %% The oldest version too...
1263	    {{0, 0}, ?VERSION}
1264    end.
1265
1266conv({More, Terms}, FileNo) when is_record(More, continuation) ->
1267    Cont = More#continuation{pos = {FileNo, More#continuation.pos}},
1268    {Cont, Terms};
1269conv({More, Terms, Bad}, FileNo) when is_record(More, continuation) ->
1270    Cont = More#continuation{pos = {FileNo, More#continuation.pos}},
1271    {Cont, Terms, Bad};
1272conv(Other, _) ->
1273    Other.
1274
1275find_first_file(#handle{filename = FName, curF = CurF, maxF = MaxF}) ->
1276    fff(FName, inc(CurF, MaxF), CurF, MaxF).
1277
1278fff(_FName, CurF, CurF, _MaxF) -> CurF;
1279fff(FName, MaybeFirstF, CurF, MaxF) ->
1280    N = add_ext(FName, MaybeFirstF),
1281    case file:read_file_info(N) of
1282	{ok, _} -> MaybeFirstF;
1283	_ -> fff(FName, inc(MaybeFirstF, MaxF), CurF, MaxF)
1284    end.
1285
1286%% -> {iolist(), LastBins, NoBytes, NoTerms}
1287ext_split_bins(CurB, MaxB, FirstPos, Bins) ->
1288    MaxBs = MaxB - CurB, IsFirst = CurB =:= FirstPos,
1289    ext_split_bins(MaxBs, IsFirst, [], Bins, 0, 0).
1290
1291-dialyzer({no_improper_lists, ext_split_bins/6}).
1292ext_split_bins(MaxBs, IsFirst, First, [X | Last], Bs, N) ->
1293    NBs = Bs + byte_size(X),
1294    if
1295        NBs =< MaxBs ->
1296	    ext_split_bins(MaxBs, IsFirst, [First | X], Last, NBs, N+1);
1297	IsFirst, First =:= [] ->
1298            % To avoid infinite loop - we allow the file to be
1299   	    % too big if it's just one item on the file.
1300	    {[X], Last, NBs, N+1};
1301	true ->
1302	    {First, [X | Last], Bs, N}
1303    end;
1304ext_split_bins(_, _, First, [], Bs, N) ->
1305    {First, [], Bs, N}.
1306
1307%% -> {iolist(), LastBins, NoBytes, NoTerms}
1308int_split_bins(CurB, MaxB, FirstPos, Bins) ->
1309    MaxBs = MaxB - CurB, IsFirst = CurB =:= FirstPos,
1310    int_split_bins(MaxBs, IsFirst, [], Bins, 0, 0).
1311
1312-dialyzer({no_improper_lists, int_split_bins/6}).
1313int_split_bins(MaxBs, IsFirst, First, [X | Last], Bs, N) ->
1314    Sz = byte_size(X),
1315    NBs = Bs + Sz + ?HEADERSZ,
1316    BSz = <<Sz:?SIZESZ/unit:8>>,
1317    XB = case Sz < ?MIN_MD5_TERM of
1318             true ->
1319                 [BSz, ?BIGMAGICHEAD | X];
1320             false ->
1321                 MD5 = erlang:md5(BSz),
1322                 [BSz, ?BIGMAGICHEAD, MD5 | X]
1323         end,
1324    if
1325        NBs =< MaxBs ->
1326	    int_split_bins(MaxBs, IsFirst, [First | XB], Last, NBs, N+1);
1327	IsFirst, First =:= [] ->
1328            % To avoid infinite loop - we allow the file to be
1329   	    % too big if it's just one item on the file.
1330	    {[XB], Last, NBs, N+1};
1331	true ->
1332	    {First, [X | Last], Bs, N}
1333    end;
1334int_split_bins(_, _, First, [], Bs, N) ->
1335    {First, [], Bs, N}.
1336
1337%% -> {NewCurrentFileNo, MaxFilesToBe} | throw(FileError)
1338inc_wrap(FName, CurF, MaxF) ->
1339    case MaxF of
1340	%% Number of max files has changed
1341	{NewMaxF, OldMaxF} ->
1342	    if
1343		CurF >= NewMaxF ->
1344		    %% We are at or above the new number of files
1345		    remove_files(FName, CurF + 1, OldMaxF),
1346		    if
1347			CurF > NewMaxF ->
1348			    %% The change was done while the current file was
1349			    %% greater than the new number of files.
1350			    %% The index file is not truncated here, since
1351			    %% writing the index file while opening the file
1352			    %% with index 1 will write the value for the file
1353			    %% with extension CurF as well. Next time the
1354			    %% limit is reached, the index file will be
1355			    %% truncated.
1356			    {1, {NewMaxF, CurF}};
1357			true ->
1358			    %% The change was done while the current file was
1359			    %% less than the new number of files.
1360			    %% Remove the files from the index file too
1361			    index_file_trunc(FName, NewMaxF),
1362			    {1, NewMaxF}
1363		    end;
1364		true ->
1365		    %% We haven't reached the new limit yet
1366		    NewFt = inc(CurF, NewMaxF),
1367		    {NewFt, MaxF}
1368	    end;
1369	MaxF ->
1370	    %% Normal case.
1371	    NewFt = inc(CurF, MaxF),
1372	    {NewFt, MaxF}
1373    end.
1374
1375inc(N, {_NewMax, OldMax}) -> inc(N, OldMax, 1);
1376inc(N, Max) -> inc(N, Max, 1).
1377
1378inc(N, Max, Step) ->
1379    Nx = (N + Step) rem Max,
1380    if
1381	Nx > 0 -> Nx;
1382	true -> Nx + Max
1383    end.
1384
1385
1386file_size(Fname) ->
1387    {ok, Fi} = file:read_file_info(Fname),
1388    Fi#file_info.size.
1389
1390%% -> ok | throw(FileError)
1391%% Tries to remove each file with name FName.I, N<=I<=Max.
1392remove_files(FName, N, Max) ->
1393    remove_files(FName, N, Max, ok).
1394
1395remove_files(_FName, N, Max, ok) when N > Max ->
1396    ok;
1397remove_files(_FName, N, Max, {FileName, Error}) when N > Max ->
1398    file_error(FileName, Error);
1399remove_files(FName, N, Max, Reply) ->
1400    FileName = add_ext(FName, N),
1401    NewReply = case file:delete(FileName) of
1402		   ok -> Reply;
1403		   {error, enoent} -> Reply;
1404		   Error -> {FileName, Error}
1405	       end,
1406    remove_files(FName, N + 1, Max, NewReply).
1407
1408%% -> {MaxBytes, MaxFiles}
1409get_wrap_size(#handle{maxB = MaxB, maxF = MaxF}) ->
1410    case MaxF of
1411	{NewMaxF,_} -> {MaxB, NewMaxF};
1412	MaxF        -> {MaxB, MaxF}
1413    end.
1414
1415add_ext(Name, Ext) ->
1416    concat([Name, ".", Ext]).
1417
1418open_read(FileName) ->
1419    file:open(FileName, [raw, binary, read]).
1420
1421open_update(FileName) ->
1422    file:open(FileName, [raw, binary, read, write]).
1423
1424open_truncate(FileName) ->
1425    file:open(FileName, [raw, binary, write]).
1426
1427%%% Functions that access files, and throw on error.
1428
1429-define(TIMEOUT, 2000). % ms
1430
1431%% -> {Reply, cache()}; Reply = ok | Error
1432fwrite(FdC, _FN, _B, 0) ->
1433    {ok, FdC};  % avoid starting a timer for empty writes
1434fwrite(#cache{fd = Fd, c = C, sz = Sz} = FdC, FileName, B, Size) ->
1435    Sz1 = Sz + Size,
1436    C1 = cache_append(C, B),
1437    if Sz1 > ?MAX_FWRITE_CACHE ->
1438            write_cache(Fd, FileName, C1);
1439       true ->
1440            maybe_start_timer(C),
1441            {ok, FdC#cache{sz = Sz1, c = C1}}
1442    end.
1443
1444cache_append([], B) -> B;
1445cache_append(C, B) -> [C | B].
1446
1447%% if the cache was empty, start timer (unless it's already running)
1448maybe_start_timer([]) ->
1449    case get(write_cache_timer_is_running) of
1450        true ->
1451            ok;
1452        _ ->
1453            put(write_cache_timer_is_running, true),
1454            erlang:send_after(?TIMEOUT, self(), {self(), write_cache}),
1455            ok
1456    end;
1457maybe_start_timer(_C) ->
1458    ok.
1459
1460fwrite_header(Fd, B, Size) ->
1461    {ok, #cache{fd = Fd, sz = Size, c = B}}.
1462
1463%% -> {NewFdC, Reply}; Reply = ok | Error
1464pread(#cache{fd = Fd, c = C}, FileName, Position, MaxBytes) ->
1465    Reply = write_cache(Fd, FileName, C),
1466    case Reply of
1467	{ok, NewFdC} ->
1468	    case file:pread(Fd, Position, MaxBytes) of
1469		{error, Error} ->
1470		    {NewFdC, catch file_error(FileName, {error, Error})};
1471		R ->
1472		    {NewFdC, R}
1473	    end;
1474	{Error, NewFdC} ->
1475	    {NewFdC, Error}
1476    end.
1477
1478%% -> {ok, cache(), Pos} | {Error, cache()}
1479position(#cache{fd = Fd, c = C}, FileName, Pos) ->
1480    Reply = write_cache(Fd, FileName, C),
1481    case Reply of
1482	{ok, NewFdC} ->
1483	    case position2(Fd, FileName, Pos) of
1484		{ok, Loc} ->
1485		    {ok, NewFdC, Loc};
1486		Error ->
1487		    {Error, NewFdC}
1488	    end;
1489	_Error ->
1490	    Reply
1491    end.
1492
1493position_close(#cache{fd = Fd, c = C}, FileName, Pos) ->
1494    NewFdC = write_cache_close(Fd, FileName, C),
1495    {ok, Loc} = position_close2(Fd, FileName, Pos),
1496    {NewFdC, Loc}.
1497
1498fsync(#cache{fd = Fd, c = C}, FileName) ->
1499    Reply = write_cache(Fd, FileName, C),
1500    case Reply of
1501	{ok, NewFdC} ->
1502	    case file:sync(Fd) of
1503		ok ->
1504		    Reply;
1505		Error ->
1506		    {catch file_error(FileName, Error), NewFdC}
1507	    end;
1508	_Error ->
1509	    Reply
1510    end.
1511
1512%% -> {Reply, NewFdC}; Reply = ok | Error
1513truncate_at(FdC, FileName, Pos) ->
1514    case position(FdC, FileName, Pos) of
1515	{ok, NewFdC, _Pos} ->
1516	    case file:truncate(NewFdC#cache.fd) of
1517		ok ->
1518		    {ok, NewFdC};
1519		Error ->
1520		    {catch file_error(FileName, Error), NewFdC}
1521	    end;
1522	Reply ->
1523	    Reply
1524    end.
1525
1526fwrite_close2(Fd, FileName, B) ->
1527    case file:write(Fd, B) of
1528	ok    -> ok;
1529	Error -> file_error_close(Fd, FileName, Error)
1530    end.
1531
1532pwrite_close2(Fd, FileName, Position, B) ->
1533    case file:pwrite(Fd, Position, B) of
1534	ok -> ok;
1535	{error,Error} -> file_error(FileName, {error, Error})
1536    end.
1537
1538position2(Fd, FileName, Pos) ->
1539    case file:position(Fd, Pos) of
1540	{error, Error} -> catch file_error(FileName, {error, Error});
1541	OK -> OK
1542    end.
1543
1544position_close2(Fd, FileName, Pos) ->
1545    case file:position(Fd, Pos) of
1546	{error, Error} -> file_error_close(Fd, FileName, {error, Error});
1547	OK -> OK
1548    end.
1549
1550truncate_at_close2(Fd, FileName, Pos) ->
1551    {ok, _} = position_close2(Fd, FileName, Pos),
1552    case file:truncate(Fd) of
1553	ok    -> ok;
1554	Error -> file_error_close(Fd, FileName, Error)
1555    end.
1556
1557fclose(#cache{fd = Fd, c = C}, FileName) ->
1558    %% The cache is empty if the file was opened in read_only mode.
1559    _ = write_cache_close(Fd, FileName, C),
1560    file:close(Fd).
1561
1562set_quiet(Bool) ->
1563    put(quiet, Bool).
1564
1565is_quiet() ->
1566    get(quiet) =:= true.
1567
1568%% -> {Reply, #cache{}}; Reply = ok | Error
1569write_cache(Fd, _FileName, []) ->
1570    {ok, #cache{fd = Fd}};
1571write_cache(Fd, FileName, C) ->
1572    case file:write(Fd, C) of
1573        ok    -> {ok, #cache{fd = Fd}};
1574        Error -> {catch file_error(FileName, Error), #cache{fd = Fd}}
1575    end.
1576
1577-spec write_cache_close(file:fd(), file:filename(), iodata()) -> #cache{}. % | throw(Error)
1578
1579write_cache_close(Fd, _FileName, []) ->
1580    #cache{fd = Fd};
1581write_cache_close(Fd, FileName, C) ->
1582    case file:write(Fd, C) of
1583        ok    -> #cache{fd = Fd};
1584        Error -> file_error_close(Fd, FileName, Error)
1585    end.
1586
1587-spec file_error(file:filename(), {'error', file:posix()}) -> no_return().
1588
1589file_error(FileName, {error, Error}) ->
1590    throw({error, {file_error, FileName, Error}}).
1591
1592-spec file_error_close(file:fd(), file:filename(), {'error', file:posix()}) -> no_return().
1593
1594file_error_close(Fd, FileName, {error, Error}) ->
1595    _ = file:close(Fd),
1596    throw({error, {file_error, FileName, Error}}).
1597