1/*  File:    canny/z.pl
    2    Author:  Roy Ratcliffe
    3    Created: Dec  3 2021
    4    Purpose: Zipped Files
    5
    6Copyright (c) 2022, Roy Ratcliffe, Northumberland, United Kingdom
    7
    8Permission is hereby granted, free of charge,  to any person obtaining a
    9copy  of  this  software  and    associated   documentation  files  (the
   10"Software"), to deal in  the   Software  without  restriction, including
   11without limitation the rights to  use,   copy,  modify,  merge, publish,
   12distribute, sublicense, and/or sell  copies  of   the  Software,  and to
   13permit persons to whom the Software is   furnished  to do so, subject to
   14the following conditions:
   15
   16    The above copyright notice and this permission notice shall be
   17    included in all copies or substantial portions of the Software.
   18
   19THE SOFTWARE IS PROVIDED "AS IS", WITHOUT  WARRANTY OF ANY KIND, EXPRESS
   20OR  IMPLIED,  INCLUDING  BUT  NOT   LIMITED    TO   THE   WARRANTIES  OF
   21MERCHANTABILITY, FITNESS FOR A PARTICULAR   PURPOSE AND NONINFRINGEMENT.
   22IN NO EVENT SHALL THE AUTHORS  OR   COPYRIGHT  HOLDERS BE LIABLE FOR ANY
   23CLAIM, DAMAGES OR OTHER LIABILITY,  WHETHER   IN  AN ACTION OF CONTRACT,
   24TORT OR OTHERWISE, ARISING FROM,  OUT  OF   OR  IN  CONNECTION  WITH THE
   25SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
   26
   27*/
   28
   29:- module(canny_z,
   30          [ enz/2,                              % +Data:list,+File
   31            unz/2                               % +File,-Data:list
   32          ]).   33:- autoload(library(memfile), [new_memory_file/1, open_memory_file/4]).   34:- autoload(library(zip), [zip_open/4, zip_close/1, zipper_file_info/3]).
 enz(+Data:list, +File) is semidet
Zips Data to File. Writes zip(Name:atom, Info:dict, MemFile:memory_file) functor triples to File where Name is the key; MemFile is the content as a memory file. Converts the Info dictionary to new-member options when building up the zipper. Ignores any non-valid key pairs, including offset plus compressed and uncompressed sizes.

The implementation asserts octet encoding for new files with a zipper. The predicate for creating a zipper member does not allow for an encoding option. It encodes as binary by default.

   49enz(Data, File) :-
   50    setup_call_cleanup(
   51        zip_open(File, write, Zipper, []),
   52        enz_(Data, Zipper),
   53        zip_close(Zipper)
   54    ).
   55
   56enz_([H|T], Zipper) :-
   57    enz__(H, Zipper),
   58    enz_(T, Zipper).
   59enz_([], _Zipper).
   60
   61enz__(zip(Name, Info, File), Zipper) :-
   62    dict_pairs(Info, zip, Pairs),
   63    new_file_in_zip_options(Pairs, Options),
   64    setup_call_cleanup(
   65        open_memory_file(File, read, In, [encoding(octet)]),
   66        setup_call_cleanup(
   67            zipper_open_new_file_in_zip(Zipper, Name, Out, Options),
   68            (   stream_property(Out, encoding(octet)),
   69                copy_stream_data(In, Out)
   70            ),
   71            close(Out)
   72        ),
   73        close(In)
   74    ).
   75
   76new_file_in_zip_options([Key-Value|T0], [Option|T]) :-
   77    new_file_in_zip_option(Key),
   78    !,
   79    Option =.. [Key, Value],
   80    new_file_in_zip_options(T0, T).
   81new_file_in_zip_options([_|T0], T) :-
   82    new_file_in_zip_options(T0, T).
   83new_file_in_zip_options([], []).
   84
   85new_file_in_zip_option(extra).
   86new_file_in_zip_option(comment).
   87new_file_in_zip_option(time).
   88new_file_in_zip_option(method).
   89new_file_in_zip_option(level).
   90new_file_in_zip_option(zip64).
 unz(+File, -Data:list) is semidet
Unzips File to Data, a list of zip functors with Name atom, Info dictionary and MemFile content arguments.

You cannot apply unz/2 to an empty zip File. A bug crashes the entire Prolog run-time virtual machine.

  100unz(File, Data) :-
  101    setup_call_cleanup(
  102        zip_open(File, read, Zipper, []),
  103        unz_(Data, Zipper),
  104        zip_close(Zipper)
  105    ).
  106
  107%   Trailing underscores represent prime. The first prime unzips the
  108%   first zipper member. Prime-prime unzips the next and any subsequent
  109%   members. Triple prime performs the member-wise opening and reading.
  110
  111unz_([H|T], Zipper) :-
  112    zipper_goto(Zipper, first),
  113    !,
  114    unz___(H, Zipper),
  115    unz__(T, Zipper).
  116unz_([], _Zipper).
  117
  118unz__([H|T], Zipper) :-
  119    zipper_goto(Zipper, next),
  120    !,
  121    unz___(H, Zipper),
  122    unz__(T, Zipper).
  123unz__([], _Zipper).
  124
  125unz___(zip(Name, Info, File), Zipper) :-
  126    zipper_file_info(Zipper, Name, Info),
  127    new_memory_file(File),
  128    setup_call_cleanup(
  129        open_memory_file(File, write, Out, [encoding(octet)]),
  130        setup_call_cleanup(
  131            zipper_open_current(Zipper, In, [type(binary)]),
  132            copy_stream_data(In, Out),
  133            close(In)
  134        ),
  135        close(Out)
  136    )