1/* Part of SWI-Prolog 2 3 Author: Jan Wielemaker 4 E-mail: J.Wielemaker@vu.nl 5 WWW: http://www.swi-prolog.org 6 Copyright (c) 2018, VU University Amsterdam 7 All rights reserved. 8 9 Redistribution and use in source and binary forms, with or without 10 modification, are permitted provided that the following conditions 11 are met: 12 13 1. Redistributions of source code must retain the above copyright 14 notice, this list of conditions and the following disclaimer. 15 16 2. Redistributions in binary form must reproduce the above copyright 17 notice, this list of conditions and the following disclaimer in 18 the documentation and/or other materials provided with the 19 distribution. 20 21 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 22 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 23 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 24 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 25 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 26 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 27 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 28 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 29 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 30 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 31 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 32 POSSIBILITY OF SUCH DAMAGE. 33*/ 34 35:- module(zip, 36 [ zip_open/4, % +File, +Mode, -Zipper, +Options 37 zip_close/1, % +Zipper 38 zip_close/2, % +Zipper, +Comment 39 % Entry predicates 40 with_zipper/2, % +Zipper, :Goal 41 zipper_open_new_file_in_zip/4, % +Zipper, +File, -Stream, +Options 42 zipper_goto/2, % +Zipper, +Where 43 zipper_open_current/3, % +Zipper, -Stream, +Options 44 zipper_members/2, % +Zipper, -Entries 45 zipper_file_info/3 % +Zipper, -Name, -Attrs 46 ]). 47:- use_module(library(error)). 48:- use_module(library(option)). 49 50:- meta_predicate 51 with_zipper( , ).
read
or
write
. The Options list is currently ignored.
80zip_open(File, Mode, Zipper, _Options) :-
81 must_be(oneof([read,write]), Mode),
82 open(File, Mode, Stream, [type(binary)]),
83 zip_open_stream(Stream, Zipper, [close_parent(true)]).
94zip_close(Zipper) :- 95 zip_close_(Zipper, _). 96zip_close(Zipper, Options) :- 97 option(comment(Comment), Options, _), 98 zip_close_(Zipper, Comment).
true
(default), release te archive for access by other
threads after the entry is closed.It is allowed to call zip_close/1 immediately after this call, in which case the archive is closed when the entry is closed.
133with_zipper(Zipper, Goal) :-
134 setup_call_cleanup(
135 zip_lock(Zipper),
136 Goal,
137 zip_unlock(Zipper)).
143zipper_members(Zipper, Members) :- 144 with_zipper(Zipper, 145 ( zipper_goto(Zipper, first), 146 zip_members_(Zipper, Members) 147 )). 148 149zip_members_(Zipper, [Name|T]) :- 150 zip_file_info_(Zipper, Name, _Attrs), 151 ( zipper_goto(Zipper, next) 152 -> zip_members_(Zipper, T) 153 ; T = [] 154 ).
176zipper_file_info(Zipper, Name, Attrs) :- 177 zip_file_info_(Zipper, Name, 178 info(CompressedSize, UnCompressedSize, 179 Extra, Comment, 180 Time, Offset)), 181 Attrs0 = zip{compressed_size:CompressedSize, 182 uncompressed_size:UnCompressedSize, 183 offset:Offset 184 }, 185 zip_attr(Extra, extra, Attrs0, Attrs1), 186 zip_attr(Comment, comment, Attrs1, Attrs2), 187 zip_attr(Time, time, Attrs2, Attrs). 188 189zip_attr("", _, Attrs, Attrs) :- !. 190zip_attr('', _, Attrs, Attrs) :- !. 191zip_attr(Value, Name, Attrs0, Attrs) :- 192 put_dict(Name, Attrs0, Value, Attrs)
Access resource ZIP archives
This library provides access to ZIP files. ZIP files are used to store SWI-Prolog resources. Ths library provides more high level access and documentation in addition to the low level access provided as built in as it is needed to bootstrap SWI-Prolog.
Access to a zip file is provided by means of a zipper object. This is a blob that is subject to atom garbage collection. Collecting a zipper closes the underlying OS access.
A zipper is a stateful object. We recognise the following states: idle, scan, read_entry, write_entry and close. The interface raise a permission_error when trying to make an illegal state transition.
Being stateful, a zipper cannot be used simultaneously from multiple threads. The zipper becomes owned by a thread when moving to scan using zipper_goto/2. It is released after zipper_open_current/3 followed by closing the stream. */