1:- module(gitty_pack,
2 [ pack_objects/2, 3 pack_objects/3, 4 attach_pack/1, 5 load_object_from_pack/4 6 ]). 7:- use_module(library(apply)). 8:- use_module(library(debug)). 9:- use_module(library(error)). 10:- use_module(library(zlib)). 11:- use_module(lib/gitty_driver_files). 12
20
21pack_version(1).
22
25
26pack_objects(Store, Pack) :-
27 findall(Object, gitty_hash(Store, Object), Objects),
28 pack_objects(Store, Objects, Pack).
29
30pack_objects(Store, Objects, Pack) :-
31 maplist(object_info(Store), Objects, Info),
32 setup_call_cleanup(
33 open(Pack, write, Out, [type(binary)]),
34 ( write_signature(Out),
35 maplist(write_header(Out), Info),
36 format(Out, 'end_of_header.~n', []),
37 maplist(add_file(Out, Store), Objects)
38 ),
39 close(Out)).
40
41object_info(Store, Object, obj(Object, Type, Size, FileSize)) :-
42 gitty_object_file(Store, Object, File),
43 load_object_header(Store, Object, Type, Size),
44 size_file(File, FileSize).
45
46write_signature(Out) :-
47 pack_version(Version),
48 format(Out, "gitty(~d).~n", [Version]).
49
(Out, obj(Object, Type, Size, FileSize)) :-
51 format(Out, 'obj(~q,~q,~d,~d).~n', [Object, Type, Size, FileSize]).
52
53add_file(Out, Store, Object) :-
54 gitty_object_file(Store, Object, File),
55 setup_call_cleanup(
56 open(File, read, In, [type(binary)]),
57 copy_stream_data(In, Out),
58 close(In)).
59
60:- dynamic
61 pack_object/5. 62
66
67attach_pack(Pack) :-
68 retractall(pack_object(_,_,_,_,Pack)),
69 setup_call_cleanup(
70 open(Pack, read, In, [type(binary)]),
71 ( read_header(In, Version, Objects),
72 get_code(In, Code),
73 assertion(Code == 0'\n),
74 byte_count(In, DataOffset)
75 ),
76 close(In)),
77 foldl(assert_object(Pack, Version), Objects, DataOffset, _).
78
(In, Version, Objects) :-
80 read(In, Signature),
81 ( Signature = gitty(Version)
82 -> true
83 ; domain_error(gitty_pack_file, Objects)
84 ),
85 read(In, Term),
86 read_index(Term, In, Objects).
87
88read_index(end_of_header, _, []) :-
89 !.
90read_index(Object, In, [Object|T]) :-
91 read(In, Term2),
92 read_index(Term2, In, T).
93
94assert_object(Pack, _Version,
95 obj(Object, Type, Size, FileSize),
96 Offset0, Offset) :-
97 Offset is Offset0+FileSize,
98 assertz(pack_object(Object, Type, Size, Offset0, Pack)).
99
101
102load_object_from_pack(Hash, Data, Type, Size) :-
103 pack_object(Hash, Type, Size, Offset, Pack),
104 setup_call_cleanup(
105 open(Pack, read, In, [type(binary)]),
106 read_object_at(In, Offset, Data, Type, Size),
107 close(In)).
108
109read_object_at(In, Offset, Data, Type, Size) :-
110 seek(In, Offset, bof, Offset),
111 set_stream(In, encoding(utf8)),
112 setup_call_cleanup(
113 zopen(In, In2, [multi_part(false), close_parent(false)]),
114 gitty_driver_files:read_object(In2, Data, Type, Size),
115 close(In2))