1:- module(
    2  archive_ext,
    3  [
    4    archive_call/2,       % +In, :Goal_2
    5    archive_extension/1,  % ?Extension
    6    archive_media_type/1, % ?MediaType
    7    archive_open/2,       % +In, -Archive
    8    archive_stream/2      % +In1, -In2
    9  ]
   10).   11:- reexport(library(archive)).

Extended support for handling archives

This module extends the support for archives in the SWI-Prolog standard library.

*/

   20:- use_module(library(yall)).   21
   22:- use_module(library(media_type)).   23
   24:- meta_predicate
   25    archive_call(+, 2).
 archive_call(+In:istream, :Goal_2) is multi
Calls `Goal_2' on a decompressed input stream that is present in the encoded input stream `In' and the metadata object `Metas'.

Supports non-deterministically iterating over all archive members.

Uses archive_open/2 to automatically process all supporter archive filters and formats.

   41archive_call(In1, Goal_2) :-
   42  setup_call_cleanup(
   43    archive_open(In1, Arch),
   44    (
   45      archive_data_stream(Arch, In2, [meta_data(Metas)]),
   46      call(Goal_2, In2, Metas)
   47    ),
   48    archive_close(Arch)
   49  ).
 archive_extension(+Extension:atom) is semidet
archive_extension(-Extension:atom) is multi
Uses the Media Type library in order to determine whether a given `Extension' is commonly used to denote an archive file.

Can also be used to enumerate such known file name extensions.

   61archive_extension(Ext) :-
   62  var(Ext), !,
   63  archive_media_type(MediaType),
   64  media_type_extension(MediaType, Ext).
   65archive_extension(Ext) :-
   66  media_type_extension(MediaType, Ext),
   67  archive_media_type(MediaType).
 archive_filter(+Filter:atom) is semidet
archive_filter(-Filter:atom) is multi
Succeeds for all and only filter-denoting atoms that are supported by the archive library.
   77archive_filter(Filter) :-
   78  archive_media_type_filter_(_, Filter).
   79archive_filter(compress).
   80archive_filter(grzip).
   81archive_filter(lrzip).
   82archive_filter(lzip).
   83archive_filter(lzma).
   84archive_filter(lzop).
   85archive_filter(rpm).
   86archive_filter(uu).
   87
   88archive_media_type_filter_(media(application/'x-bzip2',[]), bzip2).
   89archive_media_type_filter_(media(application/gzip,[]), gzip).
   90archive_media_type_filter_(media(application/'x-xz',[]), xz).
 archive_format(+Format:atom) is semidet
archive_format(-Format:atom) is multi
Succeeds for all and only format-denoting atoms that are supported by the archive library.

This predicate purposefully skips the `mtree' archive format, becasue its use results in many false positives in real-world use cases. mtree is a plain text format, and libarchive someitmes considers a regular (non-archive) text file to be of this format. Also, mtree archives are rarely used in practice, so the loss of excluding this format is not that big.

  107archive_format(Format) :-
  108  archive_media_type_format_(_, Format).
  109archive_format(ar).
  110archive_format(empty).
  111archive_format(iso9660).
  112archive_format(raw).
  113% eXtensible ARchive
  114archive_format(xar).
 archive_media_type(+MediaType:media_type) is semidet
archive_media_type(-MediaType:media_type) is multi
Succeeds for all and only those Media Types that denote an archive format. These are recorded in the Media Type library.
  124archive_media_type(MediaType) :-
  125  ground(MediaType), !,
  126  (   archive_media_type_filter_(MediaType, _)
  127  ;   archive_media_type_format_(MediaType, _)
  128  ), !.
  129archive_media_type(MediaType) :-
  130  distinct(
  131    MediaType,
  132    (   archive_media_type_filter_(MediaType, _)
  133    ;   archive_media_type_format_(MediaType, _)
  134    )
  135  ).
  136
  137archive_media_type_format_(media(application/'x-7z-compressed',[]), '7zip').
  138archive_media_type_format_(media(application/'vnd.ms-cab-compressed',[]), cab).
  139archive_media_type_format_(media(application/'x-cpio',[]), cpio).
  140archive_media_type_format_(media(application/'x-tar',[]), gnutar).
  141archive_media_type_format_(media(application/'x-lzh-compressed',[]), lha).
  142archive_media_type_format_(media(application/'vnd.rar',[]), rar).
  143archive_media_type_format_(media(application/'x-tar',[]), tar).
  144archive_media_type_format_(media(application/zip,[]), zip).
 archive_open(+In:istream, -Archive:blob) is det
Tries to open an archive of any of the supported formats, using any of the supported filters, from the input stream In.
  153archive_open(In, Archive) :-
  154  findall(format(Format), archive_format(Format), Formats),
  155  archive_open(In, Archive, Formats).
 archive_stream(+In1:istream, -In2:istream) is det
  161archive_stream(In1, In2) :-
  162  setup_call_cleanup(
  163    archive_open(In1, Archive),
  164    archive_data_stream(Archive, In2, []),
  165    archive_close(Archive)
  166  )