% This LaTeX document was generated using the LaTeX backend of PlDoc, % The SWI-Prolog documentation system \section{library(archive): Access several archive formats} \label{sec:archive} \begin{tags} \tag{See also} \url{https://github.com/libarchive/libarchive/} \end{tags} This library uses \textit{libarchive} to access a variety of archive formats. The following example lists the entries in an archive: \begin{code} list_archive(File) :- setup_call_cleanup( archive_open(File, Archive, []), ( repeat, ( archive_next_header(Archive, Path) -> format('~w~n', [Path]), fail ; ! ) ), archive_close(Archive)). \end{code} Here is an alternative way of doing this, using \predref{archive_foldl}{4}, a higher level predicate. \begin{code} list_archive2(File) :- list_archive(File, Headers), maplist(writeln, Headers). list_archive2(File, Headers) :- archive_foldl(add_header, File, Headers, []). add_header(Path, _, [Path|Paths], Paths). \end{code} Here is another example which counts the files in the archive and prints file type information, also using \predref{archive_foldl}{4}: \begin{code} print_entry(Path, Handle, Cnt0, Cnt1) :- archive_header_property(Handle, filetype(Type)), format('File ~w is of type ~w~n', [Path, Type]), Cnt1 is Cnt0 + 1. list_archive_headers(File) :- archive_foldl(print_entry, File, 0, FileCount), format('We have ~w files', [FileCount]). \end{code} \vspace{0.7cm} \begin{description} \predicate[det]{archive_open}{3}{+Data, -Archive, +Options} Wrapper around \predref{archive_open}{4} that opens the archive in read mode. \predicate[det]{archive_open}{4}{+Data, +Mode, -Archive, +Options} Open the archive in \arg{Data} and unify \arg{Archive} with a handle to the opened archive. \arg{Data} is either a file name (as accepted by \predref{open}{4}) or a stream that has been opened with the option \verb$type(binary)$. If \arg{Data} is an already open stream, the caller is responsible for closing it (but see option \verb$close_parent(true)$) and must not close the stream until after \predref{archive_close}{1} is called. \arg{Mode} is either \const{read} or \const{write}. Details are controlled by \arg{Options}. Typically, the option \verb$close_parent(true)$ is used to also close the \arg{Data} stream if the archive is closed using \predref{archive_close}{1}. For other options when reading, the defaults are typically fine - for writing, a valid format and optional filters must be specified. The option \verb$format(raw)$ must be used to process compressed streams that do not contain explicit entries (e.g., gzip'ed data) unambibuously. The \const{raw} format creates a \textit{pseudo archive} holding a single member named \const{data}. \begin{description} \termitem{close_parent}{+Boolean} If this option is \const{true} (default \const{false}), \arg{Data} stream is closed when \predref{archive_close}{1} is called on \arg{Archive}. If \arg{Data} is a file name, the default is \const{true}. \termitem{compression}{+Compression} Synomym for \verb$filter(Compression)$. Deprecated. \termitem{filter}{+Filter} Support the indicated filter. This option may be used multiple times to support multiple filters. In read mode, If no filter options are provided, \const{all} is assumed. In write mode, \const{none} is assumed. Supported values are \const{all}, \const{bzip2}, \const{compress}, \const{gzip}, \const{grzip}, \const{lrzip}, \const{lzip}, \const{lzma}, \const{lzop}, \const{none}, \const{rpm}, \const{uu} and \const{xz}. The value \const{all} is default for read, \const{none} for write. \termitem{format}{+Format} Support the indicated format. This option may be used multiple times to support multiple formats in read mode. In write mode, you must supply a single format. If no format options are provided, \const{all} is assumed for read mode. Note that \const{all} does \textbf{not} include \const{raw} and \const{mtree}. To open both archive and non-archive files, \textit{both} \verb$format(all)$ and \verb$format(raw)$ and/or \verb$format(mtree)$ must be specified. Supported values are: \const{all}, \verb$7zip$, \const{ar}, \const{cab}, \const{cpio}, \const{empty}, \const{gnutar}, \const{iso9660}, \const{lha}, \const{mtree}, \const{rar}, \const{raw}, \const{tar}, \const{xar} and \const{zip}. The value \const{all} is default for read. \end{description} Note that the actually supported compression types and formats may vary depending on the version and installation options of the underlying libarchive library. This predicate raises a domain or permission error if the (explicitly) requested format or filter is not supported. \begin{tags} \mtag{Errors}- \verb$domain_error(filter, Filter)$ if the requested filter is invalid (e.g., \const{all} for writing). \\- \verb$domain_error(format, Format)$ if the requested format type is not supported. \\- \verb$permission_error(set, filter, Filter)$ if the requested filter is not supported. \end{tags} \predicate[det]{archive_close}{1}{+Archive} Close the archive. If \verb$close_parent(true)$ was specified in \predref{archive_open}{4}, the underlying entry stream is closed too. If there is an entry opened with \predref{archive_open_entry}{2}, actually closing the archive is delayed until the stream associated with the entry is closed. This can be used to open a stream to an archive entry without having to worry about closing the archive: \begin{code} archive_open_named(ArchiveFile, EntryName, Stream) :- archive_open(ArchiveFile, Archive, []), archive_next_header(Archive, EntryName), archive_open_entry(Archive, Stream), archive_close(Archive). \end{code} \predicate[nondet]{archive_property}{2}{+Handle, ?Property} True when \arg{Property} is a property of the archive \arg{Handle}. Defined properties are: \begin{description} \termitem{filters}{List} True when the indicated filters are applied before reaching the archive format. \end{description} \predicate[semidet]{archive_next_header}{2}{+Handle, -Name} Forward to the next entry of the archive for which \arg{Name} unifies with the pathname of the entry. Fails silently if the end of the archive is reached before success. \arg{Name} is typically specified if a single entry must be accessed and unbound otherwise. The following example opens a Prolog stream to a given archive entry. Note that \textit{Stream} must be closed using \predref{close}{1} and the archive must be closed using \predref{archive_close}{1} after the data has been used. See also \predref{setup_call_cleanup}{3}. \begin{code} open_archive_entry(ArchiveFile, EntryName, Stream) :- open(ArchiveFile, read, In, [type(binary)]), archive_open(In, Archive, [close_parent(true)]), archive_next_header(Archive, EntryName), archive_open_entry(Archive, Stream). \end{code} \begin{tags} \tag{Errors} \verb$permission_error(next_header, archive, Handle)$ if a previously opened entry is not closed. \end{tags} \predicate[det]{archive_open_entry}{2}{+Archive, -Stream} Open the current entry as a stream. \arg{Stream} must be closed. If the stream is not closed before the next call to \predref{archive_next_header}{2}, a permission error is raised. \predicate{archive_set_header_property}{2}{+Archive, +Property} Set \arg{Property} of the current header. Write-mode only. Defined properties are: \begin{description} \termitem{filetype}{-Type} \arg{Type} is one of \const{file}, \const{link}, \const{socket}, \verb$character_device$, \verb$block_device$, \const{directory} or \const{fifo}. It appears that this library can also return other values. These are returned as an integer. \termitem{mtime}{-Time} True when entry was last modified at time. \termitem{size}{-Bytes} True when entry is \arg{Bytes} long. \termitem{link_target}{-Target} \arg{Target} for a link. Currently only supported for symbolic links. \end{description} \predicate{archive_header_property}{2}{+Archive, ?Property} True when \arg{Property} is a property of the current header. Defined properties are: \begin{description} \termitem{filetype}{-Type} \arg{Type} is one of \const{file}, \const{link}, \const{socket}, \verb$character_device$, \verb$block_device$, \const{directory} or \const{fifo}. It appears that this library can also return other values. These are returned as an integer. \termitem{mtime}{-Time} True when entry was last modified at time. \termitem{size}{-Bytes} True when entry is \arg{Bytes} long. \termitem{link_target}{-Target} \arg{Target} for a link. Currently only supported for symbolic links. \termitem{format}{-Format} Provides the name of the archive format applicable to the current entry. The returned value is the lowercase version of the output of \verb$archive_format_name()$. \termitem{permissions}{-Integer} True when entry has the indicated permission mask. \end{description} \predicate{archive_extract}{3}{+ArchiveFile, +Dir, +Options} Extract files from the given archive into \arg{Dir}. Supported options: \begin{description} \termitem{remove_prefix}{+Prefix} Strip \arg{Prefix} from all entries before extracting. If \arg{Prefix} is a list, then each prefix is tried in order, succeding at the first one that matches. If no prefixes match, an error is reported. If \arg{Prefix} is an atom, then that prefix is removed. \termitem{exclude}{+ListOfPatterns} Ignore members that match one of the given patterns. Patterns are handed to \predref{wildcard_match}{2}. \termitem{include}{+ListOfPatterns} Include members that match one of the given patterns. Patterns are handed to \predref{wildcard_match}{2}. The \const{exclude} options takes preference if a member matches both the \const{include} and the \const{exclude} option. \end{description} \begin{tags} \mtag{Errors}- \verb$existence_error(directory, Dir)$ if \arg{Dir} does not exist or is not a directory. \\- \verb$domain_error(path_prefix(Prefix), Path)$ if a path in the archive does not start with Prefix \tag{To be done} Add options \end{tags} \predicate[det]{archive_entries}{2}{+Archive, -Paths} True when \arg{Paths} is a list of pathnames appearing in \arg{Archive}. \predicate[nondet]{archive_data_stream}{3}{+Archive, -DataStream, +Options} True when \arg{DataStream} is a stream to a data object inside \arg{Archive}. This predicate transparently unpacks data inside \textit{possibly nested} archives, e.g., a \textit{tar} file inside a \textit{zip} file. It applies the appropriate decompression filters and thus ensures that Prolog reads the plain data from \arg{DataStream}. \arg{DataStream} must be closed after the content has been processed. Backtracking opens the next member of the (nested) archive. This predicate processes the following options: \begin{description} \termitem{meta_data}{-Data:list(dict)} If provided, \arg{Data} is unified with a list of filters applied to the (nested) archive to open the current \arg{DataStream}. The first element describes the outermost archive. Each \arg{Data} dict contains the header properties (\predref{archive_header_property}{2}) as well as the keys: \begin{description} \termitem{filters}{Filters:list(atom)} Filter list as obtained from \predref{archive_property}{2} \termitem{name}{Atom} Name of the entry. \end{description} \end{description} Non-archive files are handled as pseudo-archives that hold a single stream. This is implemented by using \predref{archive_open}{3} with the options \verb$[format(all),format(raw)]$. \predicate[det]{archive_create}{3}{+OutputFile, +InputFiles, +Options} Convenience predicate to create an archive in \arg{OutputFile} with data from a list of \arg{InputFiles} and the given \arg{Options}. Besides options supported by \predref{archive_open}{4}, the following options are supported: \begin{description} \termitem{directory}{+Directory} Changes the directory before adding input files. If this is specified, paths of input files must be relative to \arg{Directory} and archived files will not have \arg{Directory} as leading path. This is to simulate \verb$-C$ option of the \const{tar} program. \termitem{format}{+Format} Write mode supports the following formats: `7zip`, \const{cpio}, \const{gnutar}, \const{iso9660}, \const{xar} and \const{zip}. Note that a particular installation may support only a subset of these, depending on the configuration of \const{libarchive}. \end{description} \predicate{archive_foldl}{4}{:Goal, +Archive, +State0, -State} Operates like \predref{foldl}{4} but for the entries in the archive. For each member of the archive, \arg{Goal} called as `call(:\arg{Goal}, +Path, +Handle, +S0, -S1). Here, \arg{S0} is current state of the \textit{accumulator} (starting with \arg{State0}) and \arg{S1} is the next state of the accumulator, producing \arg{State} after the last member of the archive. \begin{arguments} \arg{Archive} & File name or stream to be given to archive_open/[3,4]. \\ \end{arguments} \begin{tags} \tag{See also} \predref{archive_header_property}{2}, \predref{archive_open}{4}. \end{tags} \end{description}