Skip to content

Instantly share code, notes, and snippets.

@kamahen
Last active June 3, 2022 17:40
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save kamahen/75730c90611455921d307802ec57c19e to your computer and use it in GitHub Desktop.
Save kamahen/75730c90611455921d307802ec57c19e to your computer and use it in GitHub Desktop.
library(archive) snapshot 2022-06-03
/* Part of SWI-Prolog
Author: Jan Wielemaker and Matt Lilley
E-mail: J.Wielemaker@cs.vu.nl
WWW: http://www.swi-prolog.org
Copyright (c) 2012-2019, VU University Amsterdam
All rights reserved.
Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions
are met:
1. Redistributions of source code must retain the above copyright
notice, this list of conditions and the following disclaimer.
2. Redistributions in binary form must reproduce the above copyright
notice, this list of conditions and the following disclaimer in
the documentation and/or other materials provided with the
distribution.
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
POSSIBILITY OF SUCH DAMAGE.
*/
:- module(archive,
[ archive_open/3, % +Stream, -Archive, +Options
archive_open/4, % +Stream, +Mode, -Archive, +Options
archive_create/3, % +OutputFile, +InputFileList, +Options
archive_close/1, % +Archive
archive_property/2, % +Archive, ?Property
archive_next_header/2, % +Archive, -Name
archive_open_entry/2, % +Archive, -EntryStream
archive_header_property/2, % +Archive, ?Property
archive_set_header_property/2, % +Archive, +Property
archive_extract/3, % +Archive, +Dir, +Options
archive_entries/2, % +Archive, -Entries
archive_data_stream/3, % +Archive, -DataStream, +Options
archive_foldl/4 % :Goal, +Archive, +State0, -State
]).
:- autoload(library(error),
[existence_error/2,domain_error/2,must_be/2]).
:- autoload(library(filesex),
[directory_file_path/3,make_directory_path/1]).
:- autoload(library(lists),[member/2]).
:- autoload(library(option),[option/3,option/2]).
:- meta_predicate
archive_foldl(4, +, +, -).
/** <module> Access several archive formats
This library uses _libarchive_ to access a variety of archive formats.
The following example lists the entries in an archive:
```
list_archive(File) :-
setup_call_cleanup(
archive_open(File, Archive, []),
( repeat,
( archive_next_header(Archive, Path)
-> format('~w~n', [Path]),
fail
; !
)
),
archive_close(Archive)).
```
Here is an alternative way of doing this, using archive_foldl/4, a
higher level predicate.
```
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).
```
Here is another example which counts the files in the archive and prints
file type information, also using archive_foldl/4:
```
list_archive_headers(File) :-
archive_foldl(print_entry, File, 0, FileCount),
format('There are ~w files', [FileCount]).
print_entry(Path, Handle, Cnt0, Cnt1) :-
maplist(archive_header_property(Handle),
[filetype(Type), size(Size), permissions(Permissions), mtime(Mtime)]),
format_time(string(MtimeStr), '%d %b %Y %T %z', Mtime),
format('~|File ~w~t~30| type(~w) permissions(~|~`0t~8r~4+)~|~t~d~6+ bytes ~w~n',
[Path, Type, Permissions, Size, MtimeStr]),
Cnt1 is Cnt0 + 1.
```
The normal way of calling the predicates is:
```
archive_open_stream(ParentStream, read, Archive, []),
repeat:
archive_next_header(Archive, Name),
archive_header_property(Archive, Property),
archive_open_entry(Archive, EntryStream),
<read from EntryStream>
close(EntryStream),
archive_close(Archive),
close(ParentStream)
```
For writing, it's similar, except for `write` mode instead of `read`,
archive_set_header_property/2 instead of archive_header_property/2, and
writing to EntryStream. If you don't call close(EntryStream),
archive_close(Archive), or close(ParentStream) can lead to corruption of
the archive (if close_parent(true) is specified in the options to
archive_open/4, the close(ParentStream) can be omitted).
For both reading and writing, if close_parent(bool) is specified in
archive_open_stream/4, the close(ParentStream) is done by
archive_close(Archive) - and archive_open/4 implicitly specifies
close_parent(bool) if given a file path.
If you're working with only a single entry (no repeated
archive_next_header/2, the archive_close(Archive) can be done before the
close(EntryStream) - see archive_close/2 and its definition of
archive_open_named/3 for details.
@see https://github.com/libarchive/libarchive/ */
:- use_foreign_library(foreign(archive4pl)).
%! archive_open(+Data, -Archive, +Options) is det.
%
% Wrapper around archive_open/4 that opens the archive in read mode.
archive_open(Stream, Archive, Options) :-
archive_open(Stream, read, Archive, Options).
:- predicate_options(archive_open/4, 4,
[ close_parent(boolean),
filter(oneof([all,bzip2,compress,gzip,grzip,lrzip,
lzip,lzma,lzop,none,rpm,uu,xz])),
format(oneof([all,'7zip',ar,cab,cpio,empty,gnutar,
iso9660,lha,mtree,rar,raw,tar,xar,zip]))
]).
:- predicate_options(archive_create/3, 3,
[ directory(atom),
pass_to(archive_open/4, 4)
]).
%! archive_open(+Data, +Mode, -Archive, +Options) is det.
%
% Open the archive in Data and unify Archive with a handle to the
% opened archive. Data is either a file path (as accepted by open/4)
% or a stream that has been opened with the option type(binary). If
% Data is an already open stream, the caller is responsible for
% closing it (but see option close_parent(true)) and must not close
% the stream until after archive_close/1 is called. Mode is either
% `read` or `write`. Details are controlled by Options. Typically,
% the option close_parent(true) is used to also close the Data stream
% if the archive is closed using 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
% format(raw) must be used to process compressed streams that do not
% contain explicit entries (e.g., gzip'ed data) unambibuously. The
% =raw= format creates a _pseudo archive_ holding a single member
% named =data=.
%
% Appending to an archive is not supported because the underlying
% `libarchive` does not support append (even though some formats, such
% as `zip` or uncompressed `gnutar` do support append). If you open/4
% a stream in `append` mode, you will probably create an unreadable
% archive.
%
% If the mode is =write=, archive_close/1 must be called on Archive to
% ensure that there is no data loss corruption, and must be called
% before the Data stream is closed. If you do not call
% archive_close/1, garbage collection or system shutdown will attempt
% to close the archive, but may result in data loss or corruption.
%
% * close_parent(+Boolean)
% If this option is =true= (default =false=), Data stream is closed
% when archive_close/1 is called on Archive. If Data is a file name,
% the default is =true=.
%
% * compression(+Compression)
% Synomym for filter(Compression). Deprecated.
%
% * 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, =all= is assumed. In write
% mode, =none= is assumed.
% Supported values are =all=, =bzip2=, =compress=, =gzip=,
% =grzip=, =lrzip=, =lzip=, =lzma=, =lzop=, =none=, =rpm=, =uu=
% and =xz=. The value =all= is default for read, =none= for write.
%
% * 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, =all= is assumed for read mode. Note that
% =all= does *not* include =raw= and =mtree=. To open both archive
% and non-archive files, _both_ format(all) and
% format(raw) and/or format(mtree) must be specified. Supported
% values are: =all=, =7zip=, =ar=, =cab=, =cpio=, =empty=, =gnutar=,
% =iso9660=, =lha=, =mtree=, =rar=, =raw=, =tar=, =xar= and =zip=.
% The value =all= is default for read.
%
% 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.
%
% @error domain_error if the Mode or an option isn't one of the possible values
% or if a requested filter is invalid (e.g., `all` for writing).
% @error permission_error if a format or filter isn't supported
% for the file.
% @error existence_error if the format or filter isn't supported
% in general.
archive_open(stream(Stream), Mode, Archive, Options) :-
!,
archive_open_stream(Stream, Mode, Archive, Options).
archive_open(Stream, Mode, Archive, Options) :-
is_stream(Stream),
!,
archive_open_stream(Stream, Mode, Archive, Options).
archive_open(File, Mode, Archive, Options) :-
open(File, Mode, Stream, [type(binary)]),
format(user_error, '~n***ARCHIVE_OPEN ~q ~q ~q~n~n', [File, Mode, Stream]), % DO NOT SUBMIT
catch(archive_open_stream(Stream, Mode, Archive, [close_parent(true)|Options]),
E, (close(Stream, [force(true)]), throw(E))).
%! archive_close(+Archive) is det.
%
% Close the archive. If close_parent(true) was specified in
% archive_open/4, the underlying entry stream that was passed to
% archive_open/4 is closed also. If there is an entry opened with
% 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:
%
% ```
% archive_open_named(ArchiveFile, EntryName, EntryStream) :-
% archive_open(ArchiveFile, Archive, []), % implicit close_parent(true)
% archive_next_header(Archive, EntryName),
% archive_open_entry(Archive, EntryStream),
% archive_close(Archive).
% ```
%! archive_property(+Handle, ?Property) is nondet.
%
% True when Property is a property of the archive Handle. Defined
% properties are:
%
% * filters(List)
% True when the indicated filters are applied before reaching
% the archive format.
archive_property(Handle, Property) :-
defined_archive_property(Property),
Property =.. [Name,Value],
archive_property(Handle, Name, Value).
defined_archive_property(filter(_)).
%! archive_next_header(+Handle, -Name) is semidet.
%
% Forward to the next entry of the archive for which Name unifies
% with the pathname of the entry. Fails silently if the end of
% the archive is reached before success. 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 _Stream_ must be closed using
% close/1 and the archive must be closed using archive_close/1
% after the data has been used. See also setup_call_cleanup/3.
%
% ```
% 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).
% ```
%
% @error permission_error(next_header, archive, Handle) if a
% previously opened entry is not closed.
%! archive_open_entry(+Archive, -Stream) is det.
%
% Open the current entry as a stream. Stream must be closed. If the
% stream is not closed before the next call to archive_next_header/2,
% a permission error is raised.
%
% If the mode is =write=, close/1 must be called on the Stream to
% ensure that there is no data loss corruption, and must be called
% before the Data stream is closed. Garbage collection and system
% shutdown will attempt to close the archive, but may result in data
% loss or corruption.
%
% @error permission_error if the Archive isn't in an appropriate state.
%! archive_set_header_property(+Archive, +Property)
%
% Set Property of the current header. Write-mode only. Defined
% properties are:
%
% * filetype(-Type)
% Type is one of =file=, =link=, =socket=, =character_device=,
% =block_device=, =directory= or =fifo=.
% * mtime(-Time)
% True when entry was last modified at time (as returned
% by get_time/1).
% * size(-Bytes)
% True when entry is Bytes long.
% * link_target(-Target)
% Target for a link. Currently only supported for symbolic
% links.
%
% @error permission_error if the Archive isn't in an appropriate state:
% a write-archive immediately after archive_next_header/2.
%! archive_header_property(+Archive, ?Property)
%
% True when Property is a property of the current header. Defined
% properties are:
%
% * filetype(-Type)
% Type is one of =file=, =link=, =socket=, =character_device=,
% =block_device=, =directory= or =fifo=.
% * mtime(-TimeStamp)
% True when entry was last modified at time stamp (as returned
% by get_time/1).
% * size(-Bytes)
% True when entry is Bytes long.
% * link_target(-Target)
% Target for a link. Currently only supported for symbolic
% links.
% * 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 `libarchive`'s archive_format_name().
% * permissions(-Integer)
% True when entry has the indicated permission mask.
%
% @error permission_error if the Archive isn't in an appropriate state:
% a read-archive immediately after archive_next_header/2.
archive_header_property(Archive, Property) :-
( nonvar(Property)
-> true
; header_property(Property)
),
archive_header_prop_(Archive, Property).
header_property(filetype(_)).
header_property(mtime(_)).
header_property(size(_)).
header_property(link_target(_)).
header_property(format(_)).
header_property(permissions(_)).
%! archive_extract(+ArchiveFile, +Dir, +Options)
%
% Extract files from the given archive into Dir. Supported
% options:
%
% * remove_prefix(+Prefix)
% Strip Prefix from all entries before extracting. If 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 Prefix is an atom, then that prefix is removed.
% * exclude(+ListOfPatterns)
% Ignore members that match one of the given patterns.
% Patterns are handed to wildcard_match/2.
% * include(+ListOfPatterns)
% Include members that match one of the given patterns.
% Patterns are handed to wildcard_match/2. The `exclude`
% options takes preference if a member matches both the `include`
% and the `exclude` option.
%
% @error existence_error(directory, Dir) if Dir does not exist
% or is not a directory.
% @error domain_error(path_prefix(Prefix), Path) if a path in
% the archive does not start with Prefix
% @error permission_error if the Archive isn't in an appropriate state.
% @tbd Add options
archive_extract(Archive, Dir, Options) :-
( exists_directory(Dir)
-> true
; existence_error(directory, Dir)
),
setup_call_cleanup(
archive_open(Archive, Handle, Options),
extract(Handle, Dir, Options),
archive_close(Handle)).
extract(Archive, Dir, Options) :-
archive_next_header(Archive, Path),
!,
option(include(InclPatterns), Options, ['*']),
option(exclude(ExclPatterns), Options, []),
( archive_header_property(Archive, filetype(file)),
\+ matches(ExclPatterns, Path),
matches(InclPatterns, Path)
-> archive_header_property(Archive, permissions(Perm)),
remove_prefix(Options, Path, ExtractPath),
directory_file_path(Dir, ExtractPath, Target),
file_directory_name(Target, FileDir),
make_directory_path(FileDir),
setup_call_cleanup(
archive_open_entry(Archive, In),
setup_call_cleanup(
open(Target, write, Out, [type(binary)]),
copy_stream_data(In, Out),
close(Out)),
close(In)),
set_permissions(Perm, Target)
; true
),
extract(Archive, Dir, Options).
extract(_, _, _).
%! matches(+Patterns, +Path) is semidet.
%
% True when Path matches a pattern in Patterns.
matches([], _Path) :-
!,
fail.
matches(Patterns, Path) :-
split_string(Path, "/", "/", Parts),
member(Segment, Parts),
Segment \== "",
member(Pattern, Patterns),
wildcard_match(Pattern, Segment),
!.
remove_prefix(Options, Path, ExtractPath) :-
( option(remove_prefix(Remove), Options)
-> ( is_list(Remove)
-> ( member(P, Remove),
atom_concat(P, ExtractPath, Path)
-> true
; domain_error(path_prefix(Remove), Path)
)
; ( atom_concat(Remove, ExtractPath, Path)
-> true
; domain_error(path_prefix(Remove), Path)
)
)
; ExtractPath = Path
).
%! set_permissions(+Perm:integer, +Target:atom)
%
% Restore the permissions. Currently only restores the executable
% permission.
set_permissions(Perm, Target) :-
Perm /\ 0o100 =\= 0,
!,
'$mark_executable'(Target).
set_permissions(_, _).
/*******************************
* HIGH LEVEL PREDICATES *
*******************************/
%! archive_entries(+Archive, -Paths) is det.
%
% True when Paths is a list of pathnames appearing in Archive.
archive_entries(Archive, Paths) :-
setup_call_cleanup(
archive_open(Archive, Handle, []),
contents(Handle, Paths),
archive_close(Handle)).
contents(Handle, [Path|T]) :-
archive_next_header(Handle, Path),
!,
contents(Handle, T).
contents(_, []).
%! archive_data_stream(+Archive, -DataStream, +Options) is nondet.
%
% True when DataStream is a stream to a data object inside
% Archive. This predicate transparently unpacks data inside
% _possibly nested_ archives, e.g., a _tar_ file inside a _zip_
% file. It applies the appropriate decompression filters and thus
% ensures that Prolog reads the plain data from DataStream.
% 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:
%
% - meta_data(-Data:list(dict))
% If provided, Data is unified with a list of filters applied to
% the (nested) archive to open the current DataStream. The first
% element describes the outermost archive. Each Data dict
% contains the header properties (archive_header_property/2) as
% well as the keys:
%
% - filters(Filters:list(atom))
% Filter list as obtained from archive_property/2
% - name(Atom)
% Name of the entry.
%
% Non-archive files are handled as pseudo-archives that hold a
% single stream. This is implemented by using archive_open/3 with
% the options `[format(all),format(raw)]`.
archive_data_stream(Archive, DataStream, Options) :-
option(meta_data(MetaData), Options, _),
archive_content(Archive, DataStream, MetaData, []).
archive_content(Archive, Entry, [EntryMetadata|PipeMetadataTail], PipeMetadata2) :-
archive_property(Archive, filter(Filters)),
repeat,
( archive_next_header(Archive, EntryName)
-> findall(EntryProperty,
archive_header_property(Archive, EntryProperty),
EntryProperties),
dict_create(EntryMetadata, archive_meta_data,
[ filters(Filters),
name(EntryName)
| EntryProperties
]),
( EntryMetadata.filetype == file
-> archive_open_entry(Archive, Entry0),
( EntryName == data,
EntryMetadata.format == raw
-> % This is the last entry in this nested branch.
% We therefore close the choicepoint created by repeat/0.
% Not closing this choicepoint would cause
% archive_next_header/2 to throw an exception.
!,
PipeMetadataTail = PipeMetadata2,
Entry = Entry0
; PipeMetadataTail = PipeMetadata1,
open_substream(Entry0,
Entry,
PipeMetadata1,
PipeMetadata2)
)
; fail
)
; !,
fail
).
open_substream(In, Entry, ArchiveMetadata, PipeTailMetadata) :-
setup_call_cleanup(
archive_open(stream(In),
Archive,
[ close_parent(true),
format(all),
format(raw)
]),
archive_content(Archive, Entry, ArchiveMetadata, PipeTailMetadata),
archive_close(Archive)).
%! archive_create(+OutputFile, +InputFiles, +Options) is det.
%
% Convenience predicate to create an archive in OutputFile with
% data from a list of InputFiles and the given Options.
%
% Besides options supported by archive_open/4, the following
% options are supported:
%
% * directory(+Directory)
% Changes the directory before adding input files. If this is
% specified, paths of input files must be relative to
% Directory and archived files will not have Directory
% as leading path. This is to simulate =|-C|= option of
% the =tar= program.
%
% * format(+Format)
% Write mode supports the following formats: `7zip`, `cpio`,
% `gnutar`, `iso9660`, `xar` and `zip`. Note that a particular
% installation may support only a subset of these, depending on
% the configuration of `libarchive`.
archive_create(OutputFile, InputFiles, Options) :-
must_be(list(text), InputFiles),
option(directory(BaseDir), Options, '.'),
setup_call_cleanup(
archive_open(OutputFile, write, Archive, Options),
archive_create_1(Archive, BaseDir, BaseDir, InputFiles, top),
archive_close(Archive)).
archive_create_1(_, _, _, [], _) :- !.
archive_create_1(Archive, Base, Current, ['.'|Files], sub) :-
!,
archive_create_1(Archive, Base, Current, Files, sub).
archive_create_1(Archive, Base, Current, ['..'|Files], Where) :-
!,
archive_create_1(Archive, Base, Current, Files, Where).
archive_create_1(Archive, Base, Current, [File|Files], Where) :-
directory_file_path(Current, File, Filename),
archive_create_2(Archive, Base, Filename),
archive_create_1(Archive, Base, Current, Files, Where).
archive_create_2(Archive, Base, Directory) :-
exists_directory(Directory),
!,
entry_name(Base, Directory, Directory0),
archive_next_header(Archive, Directory0),
time_file(Directory, Time),
archive_set_header_property(Archive, mtime(Time)),
archive_set_header_property(Archive, filetype(directory)),
archive_open_entry(Archive, EntryStream),
close(EntryStream),
directory_files(Directory, Files),
archive_create_1(Archive, Base, Directory, Files, sub).
archive_create_2(Archive, Base, Filename) :-
entry_name(Base, Filename, Filename0),
archive_next_header(Archive, Filename0),
size_file(Filename, Size),
time_file(Filename, Time),
archive_set_header_property(Archive, size(Size)),
archive_set_header_property(Archive, mtime(Time)),
setup_call_cleanup(
archive_open_entry(Archive, EntryStream),
setup_call_cleanup(
open(Filename, read, DataStream, [type(binary)]),
copy_stream_data(DataStream, EntryStream),
close(DataStream)),
close(EntryStream)).
entry_name('.', Name, Name) :- !.
entry_name(Base, Name, EntryName) :-
directory_file_path(Base, EntryName, Name).
%! archive_foldl(:Goal, +Archive, +State0, -State).
%
% Operates like foldl/4 but for the entries in the archive. For each
% member of the archive, Goal called as `call(:Goal, +Path, +Handle,
% +S0, -S1). Here, `S0` is current state of the _accumulator_
% (starting with State0) and `S1` is the next state of the
% accumulator, producing State after the last member of the archive.
%
% @see archive_header_property/2, archive_open/4.
%
% @arg Archive File name or stream to be given to archive_open/[3,4].
archive_foldl(Goal, Archive, State0, State) :-
setup_call_cleanup(
archive_open(Archive, Handle, [close_parent(true)]),
archive_foldl_(Goal, Handle, State0, State),
archive_close(Handle)
).
archive_foldl_(Goal, Handle, State0, State) :-
( archive_next_header(Handle, Path)
-> call(Goal, Path, Handle, State0, State1),
archive_foldl_(Goal, Handle, State1, State)
; State = State0
).
/*******************************
* MESSAGES *
*******************************/
:- multifile prolog:error_message//1.
prolog:error_message(archive_error(Code, Message)) -->
[ 'Archive error (code ~p): ~w'-[Code, Message] ].
/* Part of SWI-Prolog
Author: Jan Wielemaker
E-mail: J.Wielemaker@vu.nl
WWW: http://www.swi-prolog.org
Copyright (c) 2012-2018, VU University Amsterdam
All rights reserved.
Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions
are met:
1. Redistributions of source code must retain the above copyright
notice, this list of conditions and the following disclaimer.
2. Redistributions in binary form must reproduce the above copyright
notice, this list of conditions and the following disclaimer in
the documentation and/or other materials provided with the
distribution.
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
POSSIBILITY OF SUCH DAMAGE.
*/
#include <config.h>
#include <SWI-Stream.h>
#include <SWI-Prolog.h>
#ifdef __WINDOWS__
#define LIBARCHIVE_STATIC 1
#endif
#include <archive.h>
#include <archive_entry.h>
#include <assert.h>
#include <string.h>
#include <errno.h>
#include <ctype.h>
#include <errno.h>
#define DBG // DO NOT SUBMIT
#if ARCHIVE_VERSION_NUMBER < 3000000
/* This should never happen if cmake is set up properly */
#error "Requires libarchive 3.0.0 or later"
#endif
/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
Design of the libarchive interface
An archive is represented by a symbol (blob). The C-structure contains
the archive, the current header and some state information.
There are three kinds of "callbacks" (all indicated by the suffix
"_cb" in their names:
- Prolog blob: ar_w_{release,compare,write,acquire}_cb
- Prolog stream: ar_entry_{read,write,close,control}_cb
- libarchive "client": libarchive_{read,skip,seek,close}_cb
The foreign functions called from Prolog have the prefix "ffi_". This
is to avoid confusiong with the various archive_* functions provided
by libarchive.
The normal way of calling the predicates [`ar` is the archive_wrapper blob]:
For reading (ar->entry is allocated by archive_read_next_header):
ffi_archive_open_stream(ParentStream, read,
Archive, Options), % AR_VIRGIN -> AR_OPENED_ARCHIVE
repeat:
ffi_archive_next_header(Archive, Name), % AR_OPENED_ARCHIVE -> AR_NEW_ENTRY
ffi_archive_header_property(Archive, Property),
ffi_archive_open_entry(Archive, EntryStream), % AR_NEW_ENTRY -> AR_OPENED_ENTRY
<read from EntryStream>
close(EntryStream), % ar_entry_close_cb() % AR_OPENED_ENTRY _> AR_OPENED_ARCHIVE
ffi_archive_close(Archive), % ... -> AR_VIRGIN or AR_OPENED_ENTRY_PENDING_CLOSE
close(ParentStream) % done implicitly by ffi_archive_close(Archive) if close_parent(true)
It's similar for writing (ar->entry is allocated by
ffi_archive_entry_new()), except for `write` mode instead of
`read`, ffi_archive_set_header_property/2 instead of
ffi_archive_header_property/2, and writing to EntryStream.
Not shown are the various callbacks from either libarchive. For
example, when ffi_archive_open_stream() calls
archive_open_read1(), there is a callback to libarchive_read_cb(),
which then uses the IOSTREAM.
If close_parent(bool) is specified in archive_open_stream/4
(ffi_archive_open_stream), the close(EntryStream) is delayed until
ffi_archive_close(Archive) is called - this is indicated by state
AR_OPENED_ENTRY_PENDING_CLOSE.
For both reading and writing an archive, if
ffi_archive_close(Archive) is called before close(EntryStream),
then the status goes from AR_OPENED_ENTRY to
AR_OPENED_ENTRY_PENDING_CLOSE -- once the archive has been closed,
you can't use ffi_archive_next_header() to get another entry but
you can continue to do I/O on the stream that was created by
archive_open_entry/2.
When the blob is created (`ar`), it stores the ParentStream in
ar->data by calling PL_get_stream(). This increases the reference
count for the stream; it's decremented by
PL_release_stream(ar->data).
When an EntryStream is created (by ffi_archive_open_entry/2) and a
write is done on the stream, the following calls and callbacks
happen for write (similar for read):
prolog:write(EntryStream)
archive4pl:ar_entry_write_cb()
libarchive:archive_write_data()
archive4pl:libarchive_write_cb()
Sfwrite(ar->data)
EntryStream needs `ar`, so archive_open_entry/2 ends up calling
PL_register_atom(ar->symbol) to ensure it doesn't get gc-ed.
The close for EntryStream - ar_entry_close_cb() - calls
archive_write_finish_entry() [for write]. It also calls
PL_unregister_atom(ar->symbol).
[The documentation for archive_write_finish_entry() says that it is
implicitly called by archive_write_header() or
archive_write_close(). However, it's simpler to explicitly call it
when closing the EntryStream.]
ffi_archive_close(Archive) calls save_archive_free(), which calls
archive_{read,write}_close(), which calls libarchive_close_cb().
When the `ar` blob is released, it needs to free the
archive_entry struct, close the entry stream (EntryStream),
and close/release the archive ParentStream (ar->data).
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
#define ARCHIVE_MAGIC 348184378
typedef enum ar_status
{ AR_VIRGIN = 0,
AR_OPENED_ARCHIVE,
AR_NEW_ENTRY,
AR_OPENED_ENTRY,
AR_OPENED_ENTRY_PENDING_CLOSE, /* archive_close() was called when status == AR_OPENED_ENTRY_CLOSE */
AR_ERROR,
AR_RELEASED
} ar_status;
typedef struct archive_wrapper
{ atom_t symbol; /* Associated symbol */
IOSTREAM * data; /* Underlying stream */
unsigned int type; /* Types of formats/filters supported */
int magic; /* magic code */
ar_status status; /* Current status */
int close_parent; /* Close the parent handle */
struct archive * archive; /* Actual archive handle */
struct archive_entry *entry; /* Current entry */
int how; /* r/w mode ('r' or 'w') */
int agc; /* subject to AGC */
} archive_wrapper;
/* Convenience function - sets ar->status to AR_ERROR and returns rc.
It is intended to be wrapped around PL_xxx_error() calls. If
ar->status is set to AR_ERROR, that all further use of ar will
throw an error - this may be overkill for some errors. */
static int
ar_set_status_error(archive_wrapper *ar, int rc)
{ if ( ar && ar->status != AR_RELEASED )
ar->status = AR_ERROR;
return rc;
}
/* Convenience function - calls archive_read_free() or archive_write_free() as appropriate.
Safe to call with ar->archive == NULL.
*/
static int
safe_archive_free(archive_wrapper *ar)
{ if ( !ar || ! ar->archive )
return ARCHIVE_FATAL;
{ struct archive *archive_orig = ar->archive;
ar->archive = NULL; /* Prevent double free through callbacks */
/* TODO: this could use archive_free(archive_orig) */
switch( ar->how )
{ case 'r': return archive_read_free(archive_orig);
case 'w': return archive_write_free(archive_orig);
case ' ': return ARCHIVE_OK;
default: assert(0); return ARCHIVE_FATAL;
}
}
}
static int
close_stream(const archive_wrapper *ar, IOSTREAM *s)
{ /* Do *not* call pl_release_stream(ar_data_orig) - Sclose() or
Sgcclose() handles the release */
if ( ar->agc )
return Sgcclose(s, SIO_CLOSE_FORCE);
else
return Sclose(s);
}
static archive_wrapper archive_wrapper_init_value =
{
0, /* symbol */
NULL, /* data */
AR_VIRGIN, /* type */
ARCHIVE_MAGIC, /* magic */
AR_VIRGIN, /* status */
FALSE, /* close_parent */
NULL, /* archive */
NULL, /* entry */
' ', /* how */
FALSE /* agc */
};
/* For debugging and for ar_permission_error(): */
static const char*
ar_status_str(const archive_wrapper *ar)
{ if ( !ar )
return "AR_(null)";
switch( ar->status )
{ case AR_VIRGIN: return "AR_VIRGIN";
case AR_OPENED_ARCHIVE: return "AR_OPENED_ARCHIVE";
case AR_NEW_ENTRY: return "AR_NEW_ENTRY";
case AR_OPENED_ENTRY: return "AR_OPENED_ENTRY";
case AR_OPENED_ENTRY_PENDING_CLOSE: return "AR_OPENED_ENTRY_PENDING_CLOSE";
case AR_ERROR: return "AR_ERROR";
case AR_RELEASED: return "AR_RELEASED";
default: return "AR_???";
}
}
#ifdef DBG
static void
ar_dbg(const char *msg, const archive_wrapper *ar)
{ if ( ar )
{ Sdprintf("%-25s %p %p (%c) %-18s close_parent=%d symbol=%lu archive=%p entry=%p agc=%d\n",
msg, ar, ar->data, ar->how, ar_status_str(ar),
ar->close_parent, (long unsigned)ar->symbol, ar->archive, ar->entry, ar->agc);
assert(ar->magic == ARCHIVE_MAGIC);
} else
{ Sdprintf("%-25s %p\n", msg, ar);
}
/* Sflush(Serror); */
}
#else
static inline void
ar_dbg(const char *_msg, const archive_wrapper *_ar)
{ }
#endif
/*******************************
* CONSTANTS *
*******************************/
static atom_t ATOM_close_parent;
static atom_t ATOM_compression;
static atom_t ATOM_filter;
static atom_t ATOM_format;
static atom_t ATOM_all;
static atom_t ATOM_bzip2;
static atom_t ATOM_compress;
static atom_t ATOM_gzip;
static atom_t ATOM_grzip;
static atom_t ATOM_lrzip;
static atom_t ATOM_lzip;
static atom_t ATOM_lzma;
static atom_t ATOM_lzop;
static atom_t ATOM_none;
static atom_t ATOM_rpm;
static atom_t ATOM_uu;
static atom_t ATOM_xz;
static atom_t ATOM_7zip;
static atom_t ATOM_ar;
static atom_t ATOM_cab;
static atom_t ATOM_cpio;
static atom_t ATOM_empty;
static atom_t ATOM_gnutar;
static atom_t ATOM_iso9660;
static atom_t ATOM_lha;
static atom_t ATOM_mtree;
static atom_t ATOM_rar;
static atom_t ATOM_raw;
static atom_t ATOM_tar;
static atom_t ATOM_xar;
static atom_t ATOM_zip;
static atom_t ATOM_file;
static atom_t ATOM_link;
static atom_t ATOM_socket;
static atom_t ATOM_character_device;
static atom_t ATOM_block_device;
static atom_t ATOM_directory;
static atom_t ATOM_fifo;
static atom_t ATOM_read;
static atom_t ATOM_write;
static functor_t FUNCTOR_error2;
static functor_t FUNCTOR_archive_error4;
static functor_t FUNCTOR_existence_error3;
static functor_t FUNCTOR_filetype1;
static functor_t FUNCTOR_format1;
static functor_t FUNCTOR_mtime1;
static functor_t FUNCTOR_size1;
static functor_t FUNCTOR_link_target1;
static functor_t FUNCTOR_permissions1;
static
int PL_existence_error3(const char* type, const char* object, term_t in)
{ term_t ex = PL_new_term_ref();
if ( PL_unify_term(ex,
PL_FUNCTOR, FUNCTOR_error2,
PL_FUNCTOR, FUNCTOR_existence_error3,
PL_CHARS, type,
PL_CHARS, object,
PL_TERM, in,
PL_VARIABLE))
return PL_raise_exception(ex);
return FALSE;
}
/*******************************
* SYMBOL WRAPPER *
*******************************/
static int
ar_w_entry_alloc(archive_wrapper *ar)
{ assert(!ar->entry);
switch( ar->how )
{ case 'r':
/* archive_read_next_header() returns a pointer to something
internal to ar->archive, so nothing to free */
return TRUE;
case 'w':
ar->entry = archive_entry_new();
if ( !ar->entry )
return ar_set_status_error(ar, PL_resource_error("memory"));
return TRUE;
case ' ':
default:
assert(0);
return FALSE;
}
}
static void
ar_w_acquire_cb(atom_t symbol)
{ archive_wrapper *ar = PL_blob_data(symbol, NULL, NULL);
if ( !ar )
{ ar_dbg("AR_W_ACQUIRE_CB-null", ar);
return;
}
assert(ar->magic == ARCHIVE_MAGIC);
assert(ar->data); /* Must have been set before PL_unify_blob() */
ar->symbol = symbol; /* But don't call PL_register_atom yet */
ar_dbg("AR_W_ACQUIRE_CB", ar);
}
/* Callback from atom gc */
static int
ar_w_release_cb(atom_t symbol)
{ archive_wrapper *ar = PL_blob_data(symbol, NULL, NULL);
assert(ar->magic == ARCHIVE_MAGIC);
ar->agc = TRUE;
ar_dbg("AR_W_RELEASE_CB", ar);
/* Under normal execution, archive_close/1 will have been called and
all the fields here will be 0 or NULL. But if archive_close/1
hasn't been called, then this is clean-up from garbage
collection.
*/
/* TODO: Can we throw an exception if the following fails? */
(void)safe_archive_free(ar);
/* Only writeable archives have ar->entry allocated by archive_entry_new() */
if (ar->how == 'w')
archive_entry_free(ar->entry); /* Safe even if !ar->entry */
ar->entry = NULL;
/* TODO: what if PL_exception(0) is true? */
/* Don't do anything clever with ar->close_parent ... if there's
been an error, just leave the "parent" stream alone and it'll
eventually get cleaned up by normal garbage collection or
PL_cleanup(). And, because ar->data might have already been
cleaned up by gc, don't do anything with it. Similarly, we can't
do PL_release_stream(ar->data) because it might have already been
released but the field hasn't been null-ed. */
*ar = archive_wrapper_init_value;
ar->agc = TRUE;
ar->status = AR_RELEASED;
ar_dbg("AR_W_RELEASE_CB-done", ar);
return TRUE;
}
static int
ar_w_compare_cb(atom_t a, atom_t b)
{ const archive_wrapper *ara = PL_blob_data(a, NULL, NULL);
const archive_wrapper *arb = PL_blob_data(b, NULL, NULL);
return ( ara > arb ? 1 :
ara < arb ? -1 : 0
);
}
static int
ar_w_write_cb(IOSTREAM *s, atom_t symbol, int flags)
{ const archive_wrapper *ar = PL_blob_data(symbol, NULL, NULL);
#ifdef DBG
Sfprintf(s, "<archive>(%p %c %s)", ar, ar->how, ar_status_str(ar));
#else
Sfprintf(s, "<archive>(%p)", ar);
#endif
return TRUE;
}
static PL_blob_t archive_blob =
{ PL_BLOB_MAGIC,
0,
"archive",
ar_w_release_cb,
ar_w_compare_cb,
ar_w_write_cb,
ar_w_acquire_cb
};
/* Convenience function that adds some context info into the
permission error and returns FALSE. */
static int
ar_permission_error(const archive_wrapper *ar, const char *operation,
const char *type, term_t culprit)
{ char operation_extended[100];
snprintf(operation_extended, sizeof operation_extended,
"%s-%s(%c)",
operation, ar_status_str(ar), ar->how);
return PL_permission_error(operation_extended, type, culprit);
}
static int
get_archive(term_t t, archive_wrapper **arp)
{ PL_blob_t *type;
void *data;
if ( PL_get_blob(t, &data, NULL, &type) && type == &archive_blob && data)
{ archive_wrapper *ar = data;
assert(ar->magic == ARCHIVE_MAGIC);
switch( ar->status )
{ case AR_OPENED_ARCHIVE:
case AR_NEW_ENTRY:
case AR_OPENED_ENTRY:
case AR_OPENED_ENTRY_PENDING_CLOSE:
*arp = ar;
return TRUE;
case AR_VIRGIN:
case AR_ERROR:
case AR_RELEASED:
*arp = NULL;
return ar_set_status_error(ar, ar_permission_error(ar, "access", "closed_archive", t));
}
}
*arp = NULL;
return PL_type_error("archive", t);
}
/*******************************
* CALLBACKS *
*******************************/
/* Callback from archive_XXX_close() or (indirectly) archive_XXX_free() */
static int
libarchive_close_cb(struct archive *a, void *cdata)
{ archive_wrapper *ar = cdata;
/* This is a no-op; archive_write_close() or archive_write_free() is
called from archive_close(), and there's nothing extra that needs
to be done here. */
(void)ar;
return ARCHIVE_OK;
}
static ssize_t
libarchive_read_cb(struct archive *a, void *cdata, const void **buffer)
{ archive_wrapper *ar = cdata;
/* This callback is called in these contexts:
- from archive_read_open1() when status == AR_VIRGIN
- when getting next header: status == AR_OPENED_ARCHIVE
- from a Prolog read on an entry stream
*/
switch( ar->status )
{ case AR_ERROR:
case AR_RELEASED:
ar_dbg("LIBARCHIVE_READ_CB/status", ar); // DO NOT SUBMIT
return ar_set_status_error(ar, -1);
case AR_VIRGIN:
case AR_OPENED_ARCHIVE:
case AR_NEW_ENTRY:
case AR_OPENED_ENTRY:
case AR_OPENED_ENTRY_PENDING_CLOSE:
if ( ar->how != 'r' )
{ Sdprintf("LIBARCHIVE_READE_CB(%c): %s\n", ar->how, ar_status_str(ar)); // DO NOT SUBMIT
return ar_set_status_error(ar, -1);
}
break;
}
/* In the following code, Sfeof() call S__fillbuff() if the buffer is empty.
TODO: Why is the code written this way instead of using Sfread()?
One reason could be that apparently libarchive doesn't
provide the buffer to dump the data in so need to maintain
such a buffer ourselves and copy the data or use the
stream's buffer. Looks a little hacky. On the other hand,
there is little wrong with it and if something changes the
tests will tell us. */
if ( Sfeof(ar->data) )
{ if ( Sferror(ar->data) )
return ar_set_status_error(ar, -1);
return 0;
} else
{ ssize_t bytes = ar->data->limitp - ar->data->bufp;
*buffer = ar->data->bufp;
ar->data->bufp = ar->data->limitp;
ar->data->position->byteno += bytes;
return bytes;
}
}
static ssize_t
libarchive_write_cb(struct archive *a, void *cdata, const void *buffer, size_t n)
{ archive_wrapper *ar = cdata;
ar_dbg("LIBARCHIVE_WRITE_CB", ar);
switch( ar->status )
{ case AR_VIRGIN:
case AR_ERROR:
case AR_RELEASED:
ar_dbg("LIBARCHIVE_WRITE_CB/status", ar); // DO NOT SUBMIT
return ar_set_status_error(ar, -1);
case AR_OPENED_ARCHIVE: /* From close(EntryStream) and others */
case AR_NEW_ENTRY:
case AR_OPENED_ENTRY:
case AR_OPENED_ENTRY_PENDING_CLOSE:
if ( ar->how != 'w' )
{ ar_dbg("LIBARCHIVE_WRITE_CB/how", ar);
return ar_set_status_error(ar, -1);
}
break;
}
return Sfwrite(buffer, 1, n, ar->data);
}
static la_int64_t
libarchive_skip_cb(struct archive *a, void *cdata, la_int64_t request)
{ archive_wrapper *ar = cdata;
ar_dbg("LIBARCHIVE_SKIP_CB", ar);
switch( ar->status )
{ case AR_VIRGIN:
case AR_OPENED_ENTRY:
case AR_OPENED_ENTRY_PENDING_CLOSE:
case AR_ERROR:
case AR_RELEASED:
ar_dbg("LIBARCHIVE_SKIP_CB/status", ar);
return 0; /* cannot skip; library will read */
case AR_NEW_ENTRY:
case AR_OPENED_ARCHIVE:
if ( ar->how != 'r' )
{ ar_dbg("LIBARCHIVE_SKIP_CB/how", ar);
return ar_set_status_error(ar, -1);
}
break;
}
if ( Sseek64(ar->data, request, SIO_SEEK_CUR) == 0 )
return request;
Sclearerr(ar->data); /* TODO: why is this? */
return 0; /* cannot skip; library will read */
}
#ifdef HAVE_ARCHIVE_READ_SET_SEEK_CALLBACK
static la_int64_t
libarchive_seek_cb(struct archive *a, void *cdata, la_int64_t request, int whence)
{ archive_wrapper *ar = cdata;
int s_whence;
switch( ar->status )
{ case AR_NEW_ENTRY:
case AR_OPENED_ENTRY:
case AR_OPENED_ENTRY_PENDING_CLOSE:
case AR_ERROR:
case AR_RELEASED:
ar_dbg("LIBARCHIVE_SEEK_CB/status", ar);
return ar_set_status_error(ar, -1);
case AR_VIRGIN: /* See comment in libarchive_read_cb */
case AR_OPENED_ARCHIVE:
if ( ar->how != 'r' )
{ ar_dbg("LIBARCHIVE_SEEK_CB/how", ar);
return ar_set_status_error(ar, -1);
}
break;
}
switch (whence) {
case SEEK_SET: s_whence=SIO_SEEK_SET; break;
case SEEK_CUR: s_whence=SIO_SEEK_CUR; break;
case SEEK_END: s_whence=SIO_SEEK_END; break;
default: assert(0); return -1;
}
if ( Sseek64(ar->data, request, s_whence) == 0 ) {
return Stell64(ar->data);
}
Sclearerr(ar->data); /* JW: TODO: why is this? */
return ARCHIVE_FATAL;
}
#endif
/*******************************
* PROLOG *
*******************************/
static int
ar_error(const archive_wrapper *ar, int rc, term_t t, const char *msg)
{ int eno = ar->archive ? archive_errno(ar->archive) : 0;
const char *s = ar->archive ? archive_error_string(ar->archive) : NULL;
term_t ex;
ar_dbg("AR_ERROR", ar);
if ( PL_exception(0) )
return FALSE;
if ( eno == 0 )
eno = rc;
if ( !s )
{ switch( rc )
{ case ARCHIVE_EOF: s = "eof"; break;
case ARCHIVE_OK: s = "ok"; break;
case ARCHIVE_RETRY: s = "retry"; break;
case ARCHIVE_WARN: s = "warn"; break;
case ARCHIVE_FAILED: s = "failed"; break;
case ARCHIVE_FATAL: s = "fatal"; break;
default: s = "unknown";
}
}
if ( ( (ex = PL_new_term_ref()) &&
PL_unify_term(ex,
PL_FUNCTOR, FUNCTOR_error2,
PL_FUNCTOR, FUNCTOR_archive_error4,
PL_INT, eno,
PL_CHARS, s,
PL_TERM, t,
PL_CHARS, msg,
PL_VARIABLE) ) )
return PL_raise_exception(ex);
return FALSE;
}
#define FILTER_ALL 0x0000ffff
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FILTER_BZIP2
#define FILTER_BZIP2 0x00000001
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FILTER_COMPRESS
#define FILTER_COMPRESS 0x00000002
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FILTER_GZIP
#define FILTER_GZIP 0x00000004
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FILTER_GRZIP
#define FILTER_GRZIP 0x00000008
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FILTER_LRZIP
#define FILTER_LRZIP 0x00000010
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FILTER_LZIP
#define FILTER_LZIP 0x00000020
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FILTER_LZMA
#define FILTER_LZMA 0x00000040
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FILTER_LZOP
#define FILTER_LZOP 0x00000080
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FILTER_NONE
#define FILTER_NONE 0x00000100
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FILTER_RPM
#define FILTER_RPM 0x00000200
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FILTER_UU
#define FILTER_UU 0x00000400
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FILTER_XZ
#define FILTER_XZ 0x00000800
#endif
#define FILTER_MASK 0x0000ffff
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FORMAT_7ZIP
#define FORMAT_7ZIP 0x00010000
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FORMAT_AR
#define FORMAT_AR 0x00020000
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FORMAT_CAB
#define FORMAT_CAB 0x00040000
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FORMAT_CPIO
#define FORMAT_CPIO 0x00080000
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FORMAT_EMPTY
#define FORMAT_EMPTY 0x00100000
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FORMAT_GNUTAR
#define FORMAT_GNUTAR 0x00200000
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FORMAT_ISO9660
#define FORMAT_ISO9660 0x00400000
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FORMAT_LHA
#define FORMAT_LHA 0x00800000
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FORMAT_MTREE
#define FORMAT_MTREE 0x01000000
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FORMAT_RAR
#define FORMAT_RAR 0x02000000
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FORMAT_RAW
#define FORMAT_RAW 0x04000000
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FORMAT_TAR
#define FORMAT_TAR 0x08000000
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FORMAT_XAR
#define FORMAT_XAR 0x10000000
#endif
#ifdef HAVE_ARCHIVE_READ_SUPPORT_FORMAT_ZIP
#define FORMAT_ZIP 0x20000000
#endif
#define FORMAT_MASK 0xffff0000
#if defined(FORMAT_RAW) && defined(FORMAT_MTREE)
#define FORMAT_ALL (FORMAT_MASK&~(FORMAT_RAW|FORMAT_MTREE))
#else
/* Compile without these. Make sure the constants are as above */
#define FORMAT_ALL (FORMAT_MASK&~(0x04000000|0x01000000))
#endif
static void
enable_type(archive_wrapper *ar, int type,
int (*f)(struct archive *ar))
{ if ( (ar->type & type) )
{ if ( (*f)(ar->archive) != ARCHIVE_OK )
ar->type &= ~type;
}
}
static foreign_t
ffi_archive_open_stream(term_t data, term_t mode, term_t handle, term_t options)
{ archive_wrapper *ar;
term_t tail = PL_copy_term_ref(options);
term_t head = PL_new_term_ref();
term_t arg = PL_new_term_ref();
/* If you make any changes here, also change archive_close() */
{ archive_wrapper ar_local = archive_wrapper_init_value;
atom_t mname;
int flags;
if ( PL_get_atom_ex(mode, &mname) )
{ if ( mname == ATOM_write )
{ ar_local.how = 'w';
flags = SIO_OUTPUT;
} else if ( mname == ATOM_read )
{ ar_local.how = 'r';
flags = SIO_INPUT;
} else
{ return ar_set_status_error(&ar_local, PL_domain_error("io_mode", mode));
}
} else
{ return FALSE;
}
{ atom_t a;
/* PL_get_stream() must be before PL_unify_blob so that there's
always a valid `data` field in the blob */
if ( !PL_get_stream(data, &ar_local.data, flags) ||
// !(ar_local.data = PL_acquire_stream(ar_local.data)) || // DO NOT SUBMIT
!PL_unify_blob(handle, &ar_local, sizeof ar_local, &archive_blob) ||
!PL_get_atom_ex(handle, &a) )
return FALSE;
ar = PL_blob_data(a, NULL, NULL);
}
}
if ( !ar_w_entry_alloc(ar) ) // DO NOT SUBMIT -- this leaks with archive_close/1
return FALSE;
while( PL_get_list_ex(tail, head, tail) )
{ atom_t name;
size_t arity;
if ( !PL_get_name_arity(head, &name, &arity) ||
!PL_get_arg(1, head, arg) )
return ar_set_status_error(ar, PL_type_error("option", head));
if ( name == ATOM_compression || name == ATOM_filter )
{ atom_t c;
if ( !PL_get_atom_ex(arg, &c) )
return FALSE;
if ( ar->how == 'w' && ((ar->type & FILTER_MASK) != 0) )
return ar_set_status_error(ar, ar_permission_error(ar, "set", "filter", arg));
if ( c == ATOM_all )
{ if (ar->how == 'w')
return ar_set_status_error(ar, PL_domain_error("write_filter", arg));
ar->type |= FILTER_ALL;
}
#ifdef FILTER_BZIP2
else if ( c == ATOM_bzip2 )
ar->type |= FILTER_BZIP2;
#endif
#ifdef FILTER_COMPRESS
else if ( c == ATOM_compress )
ar->type |= FILTER_COMPRESS;
#endif
#ifdef FILTER_GZIP
else if ( c == ATOM_gzip )
ar->type |= FILTER_GZIP;
#endif
#ifdef FILTER_GRZIP
else if ( c == ATOM_grzip )
ar->type |= FILTER_GRZIP;
#endif
#ifdef FILTER_LRZIP
else if ( c == ATOM_lrzip )
ar->type |= FILTER_LRZIP;
#endif
#ifdef FILTER_LZIP
else if ( c == ATOM_lzip )
ar->type |= FILTER_LZIP;
#endif
#ifdef FILTER_LZMA
else if ( c == ATOM_lzma )
ar->type |= FILTER_LZMA;
#endif
#ifdef FILTER_LZOP
else if ( c == ATOM_lzop )
ar->type |= FILTER_LZOP;
#endif
#ifdef FILTER_NONE
else if ( c == ATOM_none )
ar->type |= FILTER_NONE;
#endif
#ifdef FILTER_RPM
else if ( c == ATOM_rpm )
ar->type |= FILTER_RPM;
#endif
#ifdef FILTER_UU
else if ( c == ATOM_uu )
ar->type |= FILTER_UU;
#endif
#ifdef FILTER_XZ
else if ( c == ATOM_xz )
ar->type |= FILTER_XZ;
#endif
else
return ar_set_status_error(ar, PL_domain_error("filter", arg));
} else if ( name == ATOM_format )
{ atom_t f;
if ( !PL_get_atom_ex(arg, &f) )
return FALSE;
if ( ar->how == 'w' && (( ar->type & FORMAT_MASK ) != 0 ) )
return ar_set_status_error(ar, ar_permission_error(ar, "set", "format", arg));
if ( f == ATOM_all )
{ if ( ar->how == 'w' )
return ar_set_status_error(ar, PL_domain_error("write_format", arg));
ar->type |= FORMAT_ALL;
}
#ifdef FORMAT_7ZIP
else if ( f == ATOM_7zip )
ar->type |= FORMAT_7ZIP;
#endif
#ifdef FORMAT_AR
else if ( f == ATOM_ar )
ar->type |= FORMAT_AR;
#endif
#ifdef FORMAT_CAB
else if ( f == ATOM_cab )
ar->type |= FORMAT_CAB;
#endif
#ifdef FORMAT_CPIO
else if ( f == ATOM_cpio )
ar->type |= FORMAT_CPIO;
#endif
#ifdef FORMAT_EMPTY
else if ( f == ATOM_empty )
ar->type |= FORMAT_EMPTY;
#endif
#ifdef FORMAT_GNUTAR
else if ( f == ATOM_gnutar )
ar->type |= FORMAT_GNUTAR;
#endif
#ifdef FORMAT_ISO9660
else if ( f == ATOM_iso9660 )
ar->type |= FORMAT_ISO9660;
#endif
#ifdef FORMAT_LHA
else if ( f == ATOM_lha )
ar->type |= FORMAT_LHA;
#endif
#ifdef FORMAT_MTREE
else if ( f == ATOM_mtree )
ar->type |= FORMAT_MTREE;
#endif
#ifdef FORMAT_RAR
else if ( f == ATOM_rar )
ar->type |= FORMAT_RAR;
#endif
#ifdef FORMAT_RAW
else if ( f == ATOM_raw )
ar->type |= FORMAT_RAW;
#endif
#ifdef FORMAT_TAR
else if ( f == ATOM_tar )
ar->type |= FORMAT_TAR;
#endif
#ifdef FORMAT_XAR
else if ( f == ATOM_xar )
ar->type |= FORMAT_XAR;
#endif
#ifdef FORMAT_ZIP
else if ( f == ATOM_zip )
ar->type |= FORMAT_ZIP;
#endif
else
return ar_set_status_error(ar, PL_domain_error("format", arg));
} else if ( name == ATOM_close_parent )
{ if ( !PL_get_bool_ex(arg, &ar->close_parent) )
return FALSE;
}
}
if ( !PL_get_nil_ex(tail) )
return FALSE;
if ( ar->how == 'r' )
{ if ( !(ar->type & FILTER_ALL) )
ar->type |= FILTER_ALL;
if ( !(ar->type & FORMAT_MASK) )
ar->type |= FORMAT_ALL;
if ( !(ar->archive = archive_read_new()) )
return ar_set_status_error(ar, PL_resource_error("memory"));
if ( (ar->type & FILTER_ALL) == FILTER_ALL )
{ archive_read_support_filter_all(ar->archive);
} else
{
#ifdef FILTER_BZIP2
enable_type(ar, FILTER_BZIP2, archive_read_support_filter_bzip2);
#endif
#ifdef FILTER_COMPRESS
enable_type(ar, FILTER_COMPRESS, archive_read_support_filter_compress);
#endif
#ifdef FILTER_GZIP
enable_type(ar, FILTER_GZIP, archive_read_support_filter_gzip);
#endif
#ifdef FILTER_GRZIP
enable_type(ar, FILTER_GRZIP, archive_read_support_filter_grzip);
#endif
#ifdef FILTER_LRZIP
enable_type(ar, FILTER_LRZIP, archive_read_support_filter_lrzip);
#endif
#ifdef FILTER_LZIP
enable_type(ar, FILTER_LZIP, archive_read_support_filter_lzip);
#endif
#ifdef FILTER_LZMA
enable_type(ar, FILTER_LZMA, archive_read_support_filter_lzma);
#endif
#ifdef FILTER_LZOP
enable_type(ar, FILTER_LZOP, archive_read_support_filter_lzop);
#endif
#ifdef FILTER_NONE
enable_type(ar, FILTER_NONE, archive_read_support_filter_none);
#endif
#ifdef FILTER_RPM
enable_type(ar, FILTER_RPM, archive_read_support_filter_rpm);
#endif
#ifdef FILTER_UU
enable_type(ar, FILTER_UU, archive_read_support_filter_uu);
#endif
#ifdef FILTER_XZ
enable_type(ar, FILTER_XZ, archive_read_support_filter_xz);
#endif
}
if ( (ar->type & FORMAT_ALL) == FORMAT_ALL )
{ archive_read_support_format_all(ar->archive);
#ifdef FORMAT_RAW
enable_type(ar, FORMAT_RAW, archive_read_support_format_raw);
#endif
} else
{
#ifdef FORMAT_7ZIP
enable_type(ar, FORMAT_7ZIP, archive_read_support_format_7zip);
#endif
#ifdef FORMAT_AR
enable_type(ar, FORMAT_AR, archive_read_support_format_ar);
#endif
#ifdef FORMAT_CAB
enable_type(ar, FORMAT_CAB, archive_read_support_format_cab);
#endif
#ifdef FORMAT_CPIO
enable_type(ar, FORMAT_CPIO, archive_read_support_format_cpio);
#endif
#ifdef FORMAT_EMPTY
enable_type(ar, FORMAT_EMPTY, archive_read_support_format_empty);
#endif
#ifdef FORMAT_GNUTAR
enable_type(ar, FORMAT_GNUTAR, archive_read_support_format_gnutar);
#endif
#ifdef FORMAT_ISO9660
enable_type(ar, FORMAT_ISO9660, archive_read_support_format_iso9660);
#endif
#ifdef FORMAT_LHA
enable_type(ar, FORMAT_LHA, archive_read_support_format_lha);
#endif
#ifdef FORMAT_MTREE
enable_type(ar, FORMAT_MTREE, archive_read_support_format_mtree);
#endif
#ifdef FORMAT_RAR
enable_type(ar, FORMAT_RAR, archive_read_support_format_rar);
#endif
#ifdef FORMAT_RAW
enable_type(ar, FORMAT_RAW, archive_read_support_format_raw);
#endif
#ifdef FORMAT_TAR
enable_type(ar, FORMAT_TAR, archive_read_support_format_tar);
#endif
#ifdef FORMAT_XAR
enable_type(ar, FORMAT_XAR, archive_read_support_format_xar);
#endif
#ifdef FORMAT_ZIP
enable_type(ar, FORMAT_ZIP, archive_read_support_format_zip);
#endif
}
archive_read_set_callback_data(ar->archive, ar);
/* open callback is "legacy ... and should not be used" */
archive_read_set_read_callback(ar->archive, libarchive_read_cb);
archive_read_set_skip_callback(ar->archive, libarchive_skip_cb);
#ifdef HAVE_ARCHIVE_READ_SET_SEEK_CALLBACK
archive_read_set_seek_callback(ar->archive, libarchive_seek_cb);
#endif
archive_read_set_close_callback(ar->archive, libarchive_close_cb);
{ int rc = archive_read_open1(ar->archive);
if ( rc == ARCHIVE_OK )
{ ar->status = AR_OPENED_ARCHIVE;
return TRUE;
} else
{ return ar_set_status_error(ar, ar_error(ar, rc, data, "archive_read_open1"));
}
}
} else if ( ar->how == 'w' )
{ if ( !(ar->archive = archive_write_new()) )
return ar_set_status_error(ar, PL_resource_error("memory"));
/* Prevent libarchive from padding the last block to 10240 bytes. Some decompressors,
notably Oracle's jar decompressor, fail when presented with this */
archive_write_set_bytes_in_last_block(ar->archive, 1);
if (0) {}
#ifdef FORMAT_7ZIP
else if ( ar->type & FORMAT_7ZIP ) archive_write_set_format_7zip(ar->archive);
#endif
#ifdef FORMAT_CPIO
else if ( ar->type & FORMAT_CPIO ) archive_write_set_format_cpio(ar->archive);
#endif
#ifdef FORMAT_GNUTAR
else if ( ar->type & FORMAT_GNUTAR ) archive_write_set_format_gnutar(ar->archive);
#endif
#ifdef FORMAT_ISO9660
else if ( ar->type & FORMAT_ISO9660 ) archive_write_set_format_iso9660(ar->archive);
#endif
#ifdef FORMAT_XAR
else if ( ar->type & FORMAT_XAR ) archive_write_set_format_xar(ar->archive);
#endif
#ifdef FORMAT_ZIP
else if ( ar->type & FORMAT_ZIP ) archive_write_set_format_zip(ar->archive);
#endif
else
{ return ar_set_status_error(ar, PL_existence_error3("option", "format", options));
}
if (0) {}
#ifdef FILTER_BZIP2
else if ( ar->type & FILTER_BZIP2 ) archive_write_add_filter_bzip2(ar->archive);
#endif
#ifdef FILTER_COMPRESS
else if ( ar->type & FILTER_COMPRESS ) archive_write_add_filter_none(ar->archive);
#endif
#ifdef FILTER_GZIP
else if ( ar->type & FILTER_GZIP ) archive_write_add_filter_gzip(ar->archive);
#endif
#ifdef FILTER_GRZIP
else if ( ar->type & FILTER_GRZIP ) archive_write_add_filter_grzip(ar->archive);
#endif
#ifdef FILTER_LRZIP
else if ( ar->type & FILTER_LRZIP ) archive_write_add_filter_lrzip(ar->archive);
#endif
#ifdef FILTER_LZMA
else if ( ar->type & FILTER_LZMA ) archive_write_add_filter_lzma(ar->archive);
#endif
#ifdef FILTER_LZOP
else if ( ar->type & FILTER_LZMA ) archive_write_add_filter_lzop(ar->archive);
#endif
#ifdef FILTER_XZ
else if ( ar->type & FILTER_XZ ) archive_write_add_filter_xz(ar->archive);
#endif
#ifdef FILTER_NONE
else archive_write_add_filter_none(ar->archive);
#else
else
{ return ar_set_status_error(ar, PL_existence_error3("option", "filter", options));
}
#endif
{ int rc = archive_write_open(ar->archive, ar,
NULL, libarchive_write_cb, libarchive_close_cb);
if ( rc == ARCHIVE_OK )
{ ar->status = AR_OPENED_ARCHIVE;
return TRUE;
} else
{ return ar_set_status_error(ar, ar_error(ar, rc, data, "archive_write_open"));
}
}
} else {
assert(0); /* ar->how isn't 'r' or 'w' */
return FALSE;
}
}
static foreign_t
ffi_archive_property(term_t archive, term_t prop, term_t value)
{ archive_wrapper *ar;
atom_t pn;
const char *s;
if ( !get_archive(archive, &ar) ||
!PL_get_atom_ex(prop, &pn) )
return FALSE;
if ( pn == ATOM_filter )
{ int i, fcount = archive_filter_count(ar->archive);
term_t tail = PL_copy_term_ref(value);
term_t head = PL_new_term_ref();
for(i=0; i<fcount; i++)
{ s = archive_filter_name(ar->archive, i);
if ( !s || strcmp(s, "none") == 0 )
continue;
if ( !PL_unify_list(tail, head, tail) ||
!PL_unify_atom_chars(head, s) )
return FALSE;
}
return PL_unify_nil(tail);
}
return FALSE;
}
static foreign_t
ffi_archive_next_header(term_t archive, term_t name)
{ archive_wrapper *ar;
int rc;
if ( !get_archive(archive, &ar) )
{ ar_dbg("ARCHIVE_NEXT_HEADER", NULL);
return FALSE;
}
ar_dbg("ARCHIVE_NEXT_HEADER", ar);
// DO NOT SUBMIT: switch( ar->status )
switch ( ar->status )
{ case AR_OPENED_ARCHIVE:
case AR_NEW_ENTRY:
break;
case AR_VIRGIN:
case AR_OPENED_ENTRY:
case AR_OPENED_ENTRY_PENDING_CLOSE:
case AR_ERROR:
case AR_RELEASED:
return ar_set_status_error(ar, ar_permission_error(ar, "next_header", "archive", archive));
}
if ( ar->how == 'w' )
{ char* pathname = NULL;
if ( !PL_get_atom_chars(name, &pathname) )
return ar_set_status_error(ar, PL_type_error("atom", name));
archive_entry_clear(ar->entry);
archive_entry_set_pathname(ar->entry, pathname);
/* libarchive-3.1.2 does not tolerate an empty size with zip. Later versions may though - it is fixed in git as of Dec 2013.
* For now, set the other entries to a sensible default
*/
archive_entry_unset_size(ar->entry);
archive_entry_set_filetype(ar->entry, AE_IFREG);
archive_entry_set_perm(ar->entry, 0644);
ar->status = AR_NEW_ENTRY;
return TRUE;
}
assert(ar->how == 'r');
if ( ar->status == AR_NEW_ENTRY )
{ if ( (rc=archive_read_data_skip(ar->archive)) != ARCHIVE_OK )
return ar_set_status_error(ar, ar_error(ar, rc, archive, "archive_read_data_skip"));
} else
assert(ar->status == AR_OPENED_ARCHIVE);
while ( (rc=archive_read_next_header(ar->archive, &ar->entry)) == ARCHIVE_OK )
{ if ( PL_exception(0) ) /* shouldn't happen, but the callbacks are complicated */
{ ar->status = AR_ERROR;
return FALSE;
}
if ( PL_unify_wchars(name, PL_ATOM, -1,
archive_entry_pathname_w(ar->entry)) )
{ ar->status = AR_NEW_ENTRY;
return TRUE;
}
if ( PL_exception(0) ) /* e.g. resource error in PL_unify_wchars */
return FALSE;
}
if ( rc == ARCHIVE_EOF )
{ ar->status = AR_OPENED_ARCHIVE;
return FALSE; /* simply at the end */
}
return ar_set_status_error(ar, ar_error(ar, rc, archive, "archive_read_next_header"));
}
/* Called from archive_close() [Prolog archive_close/1] or
ar_entry_close_cb() [Prolog close/1] */
static int /* 0 for success, -1 for error */
ffi_archive_close_(archive_wrapper *ar)
{ int success = 0;
ar_dbg("ARCHIVE_CLOSE_", ar);
if ( !ar )
{ errno = EFAULT;
return -1;
}
/* This is the inverse of archive_open_stream().
It's essentially the same as ar_w_clear(), except it also sets
error statuses, because it's being called from Prolog. */
/* TODO: set error indication (errno, Sseterr(), Sset_exception() */
switch( ar->status )
{ case AR_VIRGIN:
case AR_NEW_ENTRY:
case AR_ERROR:
case AR_RELEASED:
case AR_OPENED_ENTRY_PENDING_CLOSE:
errno = EBADF;
success = -1;
break;
case AR_OPENED_ARCHIVE:
break;
case AR_OPENED_ENTRY:
ar->status = AR_OPENED_ENTRY_PENDING_CLOSE;
/* ar_entry_close_cb() will call archive_close_() with status
AR_OPENED_ARCHIVE if AR_OPENED_ENTRY_PENDING_CLOSE. */
return TRUE;
}
/* safe_archive_free() flushes the archive buffers, so must
be done while the ParentStream (ar->data) is still open. */
if ( safe_archive_free(ar) != ARCHIVE_OK )
{ errno = EFAULT;
success = -1;
}
ar->archive = NULL;
/* Only writeable archives have ar->entry allocated by archive_entry_new() */
if (ar->how == 'w')
archive_entry_free(ar->entry); /* Safe even if !ar->entry */
ar->entry = NULL;
if ( ar->data )
{ IOSTREAM *ar_data_orig = ar->data;
ar->data = NULL;
if ( ar->close_parent )
{ if ( close_stream(ar, ar_data_orig) != 0 )
{ if ( ar->archive )
archive_set_error(ar->archive, errno, "Close failed");
success = -1;
}
/* Do *not* call pl_release_stream(ar_data_orig) - Sclose()
handles the release */
}
}
if ( success == 0 )
ar->status = AR_VIRGIN;
else
ar->status = AR_ERROR;
return success;
}
static foreign_t
ffi_archive_close(term_t archive)
{ archive_wrapper *ar;
if ( !get_archive(archive, &ar) )
{ ar_dbg("ARCHIVE_CLOSE", NULL);
return FALSE;
}
ar_dbg("ARCHIVE_CLOSE", ar);
(void)ffi_archive_close_(ar);
if ( PL_exception(0) )
PL_clear_exception();
return TRUE;
}
/*******************************
* HEADERS *
*******************************/
static foreign_t
ffi_archive_header_prop_(term_t archive, term_t field)
{ archive_wrapper *ar;
functor_t prop;
if ( !get_archive(archive, &ar) )
return FALSE;
if ( !PL_get_functor(field, &prop) )
return ar_set_status_error(ar, PL_type_error("compound", field));
if ( ar->status != AR_NEW_ENTRY )
return ar_set_status_error(ar, ar_permission_error(ar, "access", "archive_entry", archive));
if ( ar->how != 'r' )
return ar_set_status_error(ar, ar_permission_error(ar, "read", "archive_entry", archive));
if ( prop == FUNCTOR_filetype1 )
{ __LA_MODE_T type = archive_entry_filetype(ar->entry);
atom_t name;
term_t arg = PL_new_term_ref();
_PL_get_arg(1, field, arg);
switch(type&AE_IFMT)
{ case AE_IFREG: name = ATOM_file; break;
case AE_IFLNK: name = ATOM_link; break;
case AE_IFSOCK: name = ATOM_socket; break;
case AE_IFCHR: name = ATOM_character_device; break;
case AE_IFBLK: name = ATOM_block_device; break;
case AE_IFDIR: name = ATOM_directory; break;
case AE_IFIFO: name = ATOM_fifo; break;
default:
return PL_unify_integer(arg, (type&AE_IFMT));
}
return PL_unify_atom(arg, name);
} else if ( prop == FUNCTOR_mtime1 )
{ time_t stamp = archive_entry_mtime(ar->entry);
term_t arg = PL_new_term_ref();
_PL_get_arg(1, field, arg);
return PL_unify_float(arg, (double)stamp);
} else if ( prop == FUNCTOR_size1 )
{ int64_t size = archive_entry_size(ar->entry);
term_t arg = PL_new_term_ref();
_PL_get_arg(1, field, arg);
return PL_unify_int64(arg, size);
} else if ( prop == FUNCTOR_link_target1 )
{ __LA_MODE_T type = archive_entry_filetype(ar->entry);
const wchar_t *target = NULL;
switch(type&AE_IFMT)
{ case AE_IFLNK:
target = archive_entry_symlink_w(ar->entry);
break;
}
if ( target )
{ term_t arg = PL_new_term_ref();
_PL_get_arg(1, field, arg);
return PL_unify_wchars(arg, PL_ATOM, (size_t)-1, target);
}
return FALSE;
} else if ( prop == FUNCTOR_permissions1 )
{ __LA_MODE_T perm = archive_entry_perm(ar->entry);
term_t arg = PL_new_term_ref();
_PL_get_arg(1, field, arg);
return PL_unify_integer(arg, perm);
} else if ( prop == FUNCTOR_format1 )
{ const char *s = archive_format_name(ar->archive);
if ( s )
{ char lwr[100];
char *o;
term_t arg = PL_new_term_ref();
strncpy(lwr, s, sizeof lwr - 1);
lwr[sizeof lwr - 1] = '\0';
for(o=lwr; *o; ++o)
*o = tolower(*o);
_PL_get_arg(1, field, arg);
return PL_unify_atom_chars(arg, lwr);
}
}
return ar_set_status_error(ar, PL_domain_error("archive_header_property", field));
}
static foreign_t
ffi_archive_set_header_property(term_t archive, term_t field)
{ archive_wrapper *ar;
functor_t prop;
if ( !get_archive(archive, &ar) )
return FALSE;
if ( !PL_get_functor(field, &prop) )
return ar_set_status_error(ar, PL_type_error("compound", field));
if ( ar->status != AR_NEW_ENTRY )
return ar_set_status_error(ar, ar_permission_error(ar, "access", "archive_entry", archive));
if ( ar->how != 'w' )
return ar_set_status_error(ar, ar_permission_error(ar, "write", "archive_entry", archive));
if ( prop == FUNCTOR_filetype1 )
{ atom_t name;
term_t arg = PL_new_term_ref();
__LA_MODE_T type;
_PL_get_arg(1, field, arg);
if ( !PL_get_atom(arg, &name) )
return ar_set_status_error(ar, PL_type_error("atom", arg));
if (name == ATOM_file) type = AE_IFREG;
else if (name == ATOM_link) type = AE_IFLNK;
else if (name == ATOM_socket) type = AE_IFSOCK;
else if (name == ATOM_character_device) type = AE_IFCHR;
else if (name == ATOM_block_device) type = AE_IFBLK;
else if (name == ATOM_directory) type = AE_IFDIR;
else if (name == ATOM_fifo) type = AE_IFIFO;
else
return ar_set_status_error(ar, PL_domain_error("filetype", arg));
archive_entry_set_filetype(ar->entry, type);
PL_succeed;
} else if (prop == FUNCTOR_mtime1)
{ double mtime;
term_t arg = PL_new_term_ref();
_PL_get_arg(1, field, arg);
if ( !PL_get_float(arg, &mtime) )
return ar_set_status_error(ar, PL_type_error("float", arg));
archive_entry_set_mtime(ar->entry, (time_t)mtime, 0);
PL_succeed;
} else if (prop == FUNCTOR_size1)
{ int64_t size;
term_t arg = PL_new_term_ref();
_PL_get_arg(1, field, arg);
if ( !PL_get_int64(arg, &size) )
return ar_set_status_error(ar, PL_type_error("size", arg));
archive_entry_set_size(ar->entry, size);
PL_succeed;
} else if (prop == FUNCTOR_link_target1)
{ const wchar_t* link;
atom_t atom;
size_t len;
term_t arg = PL_new_term_ref();
_PL_get_arg(1, field, arg);
if ( !PL_get_atom(arg, &atom) )
return ar_set_status_error(ar, PL_type_error("atom", arg));
link = PL_atom_wchars(atom, &len);
archive_entry_copy_symlink_w(ar->entry, link);
archive_entry_set_filetype(ar->entry, AE_IFLNK);
PL_succeed;
} else
return ar_set_status_error(ar, PL_domain_error("archive_header_property", field));
}
/*******************************
* READ MEMBERS *
*******************************/
static ssize_t
ar_entry_read_cb(void *handle, char *buf, size_t size)
{ const archive_wrapper *ar = handle;
ar_dbg("AR_ENTRY_READ_CB", ar);
if ( !ar || ! ar->archive )
return -1;
switch( ar->status )
{ case AR_VIRGIN:
case AR_OPENED_ARCHIVE:
case AR_NEW_ENTRY:
case AR_ERROR:
case AR_RELEASED:
return -1;
case AR_OPENED_ENTRY:
case AR_OPENED_ENTRY_PENDING_CLOSE:
break;
}
return archive_read_data(ar->archive, buf, size);
}
static ssize_t
ar_entry_write_cb(void *handle, char *buf, size_t size)
{ const archive_wrapper *ar = handle;
ar_dbg("AR_ENTRY_WRITE_CB", ar);
if ( !ar || ! ar->archive )
return -1;
switch( ar->status )
{ case AR_VIRGIN:
case AR_OPENED_ARCHIVE:
case AR_NEW_ENTRY:
case AR_ERROR:
case AR_RELEASED:
return -1;
case AR_OPENED_ENTRY:
case AR_OPENED_ENTRY_PENDING_CLOSE:
break;
}
size_t written = archive_write_data(ar->archive, buf, size);
/* In older version of libarchive (at least until 3.1.12), archive_write_data returns 0 for
some formats if the file size is not set. It does not set archive_errno(), unfortunately.
We turn this into an IO error here by returning -1
*/
if (written == 0 && size > 0)
{ errno = ENOSPC;
return -1;
}
return written;
}
/* Callback from Prolog close/1 */
/* See also libarchive_close_cb(), ar_w_release_cb() */
static int
ar_entry_close_cb(void *handle)
{ int success = 0;
archive_wrapper *ar = handle;
ar_dbg("AR_ENTRY_CLOSE_CB", ar);
/* This is the inverse of archive_open_entry/2, and is called from
ar_entry_close_cb(), by Prolog's close(EntryStream). The
EntryStream is derived from the stream used to create the archive
and will be taken care of by archive_close(Archive), which will
close ar->data.
*/
if ( !ar )
return -1;
/* It is possible that archive_close(Archive) was called before
close(EntryStream) - see the archive_open_named/3 example in the
documentation for archive_close/1. If archive_close(Archive) has
been called, the state is AR_OPENED_ENTRY_PENDING_CLOSE; if not,
the state is AR_OPENED_ENTRY; all other states are an error.
*/
switch( ar->status )
{ case AR_VIRGIN:
case AR_OPENED_ARCHIVE:
case AR_NEW_ENTRY:
case AR_ERROR:
case AR_RELEASED:
return -1; /* TODO: throw an error? */
case AR_OPENED_ENTRY:
break;
case AR_OPENED_ENTRY_PENDING_CLOSE:
break;
}
switch( ar->how )
{ case 'w':
if ( ar->archive && ARCHIVE_OK != archive_write_finish_entry(ar->archive) )
{ ar->status = AR_ERROR;
/* TODO: PL_exception(0) and/or ar_error()? */
success = -1;
}
break;
case 'r':
case ' ':
break;
}
if ( ar->status == AR_OPENED_ENTRY_PENDING_CLOSE )
{ /* Re-do archive_close(), this time as if the close(EntryStream)
has been done. */
ar->status = AR_OPENED_ARCHIVE;
success = ffi_archive_close_(ar);
}
ar_dbg("AR_ENTRY_CLOSE_CB/2", ar);
PL_unregister_atom(ar->symbol);
ar->status = AR_OPENED_ARCHIVE;
return success;
}
static int
ar_entry_control_cb(void *handle, int op, void *data)
{ const archive_wrapper *ar = handle;
(void)ar;
switch(op)
{ case SIO_SETENCODING:
return 0; /* allow switching encoding */
case SIO_GETSIZE:
*((int64_t*)data) = archive_entry_size(ar->entry);
return 0;
case SIO_FLUSHOUTPUT:
return 0;
default:
return -1;
}
}
static IOFUNCTIONS ar_entry_read_functions =
{ ar_entry_read_cb,
NULL, /* write */
NULL, /* seek */
ar_entry_close_cb,
ar_entry_control_cb, /* control */
NULL, /* seek64 */
};
static IOFUNCTIONS ar_entry_write_functions =
{ NULL, /* read */
ar_entry_write_cb,
NULL, /* seek */
ar_entry_close_cb,
ar_entry_control_cb, /* control */
NULL, /* seek64 */
};
static foreign_t
ffi_archive_open_entry(term_t archive, term_t stream)
{ archive_wrapper *ar;
IOSTREAM *entry_data;
/* If you make changes here, be sure to also change ar_entry_close() */
if ( !get_archive(archive, &ar) )
{ ar_dbg("ARCHIVE_OPEN_ENTRY", NULL);
return FALSE;
}
ar_dbg("ARCHIVE_OPEN_ENTRY", ar);
switch( ar->status )
{ case AR_VIRGIN:
case AR_OPENED_ARCHIVE:
case AR_OPENED_ENTRY:
case AR_OPENED_ENTRY_PENDING_CLOSE:
case AR_ERROR:
case AR_RELEASED:
return ar_set_status_error(ar, ar_permission_error(ar, "access", "archive_entry", archive));
case AR_NEW_ENTRY:
break;
}
switch ( ar->how )
{ case 'r':
entry_data = Snew(ar, SIO_INPUT|SIO_RECORDPOS, &ar_entry_read_functions);
break;
case 'w':
{ /* Finalize the header before trying to write the data */
int rc = archive_write_header(ar->archive, ar->entry);
if ( rc != ARCHIVE_OK )
return ar_set_status_error(ar, ar_error(ar, rc, archive, "archive_write_header"));
/* Then we can make a handle for the data */
entry_data = Snew(ar, SIO_OUTPUT|SIO_RECORDPOS, &ar_entry_write_functions);
}
break;
default:
assert(0);
entry_data = NULL;
}
if ( entry_data )
{ if ( PL_unify_stream(stream, entry_data) )
{ PL_register_atom(ar->symbol); /* Make sure archive's stream isn't gc-ed */
ar->status = AR_OPENED_ENTRY;
return TRUE; /* archive itself */
}
if ( close_stream(ar, entry_data) != 0 )
{ if ( ar->archive )
archive_set_error(ar->archive, errno, "Close failed");
}
/* Do *not* call pl_release_stream(ar_data_orig) - Sclose()
handles the release */
ar->status = AR_ERROR;
return FALSE;
}
return ar_set_status_error(ar, PL_resource_error("memory")); /* The only reason why Snew() fails */
}
/*******************************
* INSTALL *
*******************************/
#define MKFUNCTOR(n,a) \
FUNCTOR_ ## n ## a = PL_new_functor(PL_new_atom(#n), a)
#define MKATOM(n) \
ATOM_ ## n = PL_new_atom(#n)
install_t
install_archive4pl(void)
{ MKATOM(close_parent);
MKATOM(compression);
MKATOM(filter);
MKATOM(format);
MKATOM(all);
MKATOM(bzip2);
MKATOM(compress);
MKATOM(gzip);
MKATOM(grzip);
MKATOM(lrzip);
MKATOM(lzip);
MKATOM(lzma);
MKATOM(lzop);
MKATOM(none);
MKATOM(rpm);
MKATOM(uu);
MKATOM(xz);
ATOM_7zip = PL_new_atom("7zip");
MKATOM(ar);
MKATOM(cab);
MKATOM(cpio);
MKATOM(empty);
MKATOM(gnutar);
MKATOM(iso9660);
MKATOM(lha);
MKATOM(mtree);
MKATOM(rar);
MKATOM(raw);
MKATOM(tar);
MKATOM(xar);
MKATOM(zip);
MKATOM(file);
MKATOM(link);
MKATOM(socket);
MKATOM(character_device);
MKATOM(block_device);
MKATOM(directory);
MKATOM(fifo);
MKATOM(write);
MKATOM(read);
MKFUNCTOR(error, 2);
MKFUNCTOR(archive_error, 4);
MKFUNCTOR(existence_error, 3);
MKFUNCTOR(filetype, 1);
MKFUNCTOR(mtime, 1);
MKFUNCTOR(size, 1);
MKFUNCTOR(link_target, 1);
MKFUNCTOR(format, 1);
MKFUNCTOR(permissions, 1);
PL_register_foreign("archive_open_stream", 4, ffi_archive_open_stream, 0);
PL_register_foreign("archive_property", 3, ffi_archive_property, 0);
PL_register_foreign("archive_close", 1, ffi_archive_close, 0);
PL_register_foreign("archive_next_header", 2, ffi_archive_next_header, 0);
PL_register_foreign("archive_header_prop_", 2, ffi_archive_header_prop_, 0);
PL_register_foreign("archive_set_header_property", 2, ffi_archive_set_header_property, 0);
PL_register_foreign("archive_open_entry", 2, ffi_archive_open_entry, 0);
}
-*- mode: compilation; default-directory: "~/src/swipl-devel/src/os/" -*-
Compilation started at Thu Jun 2 16:33:17
mkdir -p ~/src/swipl-devel/build.sanitize && cd ~/src/swipl-devel/build.sanitize && cmake -G Ninja -DCMAKE_BUILD_TYPE=Sanitize -DBUILD_PDF_DOCUMENTATION=OFF -DTEST_PROTOBUFS_PROTOC=OFF -DLibArchive_LIBRARIES=/home/peter/src/libarchive/libarchive/libarchive.so -DLibArchive_INCLUDE_DIRS=/home/peter/src/libarchive/libarchive .. && ninja && ASAN_OPTIONS=detect_leaks=1 ctest -j 5 -V -R archive
-- Configuring SWI-Prolog-8.5.12
-- Configuring done
-- Generating done
-- Build files have been written to: /home/peter/src/swipl-devel/build.sanitize
[1/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-bag.c.o
[2/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-atom.c.o
[3/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-error.c.o
[4/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-zip.c.o
[5/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-dwim.c.o
[6/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-ext.c.o
[7/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-funct.c.o
[8/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-flag.c.o
[9/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-arith.c.o
[10/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-privitf.c.o
[11/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-list.c.o
[12/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-string.c.o
[13/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-load.c.o
[14/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-modul.c.o
[15/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-gc.c.o
[16/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-op.c.o
[17/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-comp.c.o
[18/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-prof.c.o
[19/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-pro.c.o
[20/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-prims.c.o
[21/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-proc.c.o
[22/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-setup.c.o
[23/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-util.c.o
[24/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-sys.c.o
[25/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-rec.c.o
[26/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-term.c.o
[27/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-read.c.o
[28/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-trace.c.o
[29/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-wic.c.o
[30/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-xterm.c.o
[31/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-wam.c.o
[32/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-write.c.o
[33/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-attvar.c.o
[34/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-gvar.c.o
[35/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-btree.c.o
[36/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-srcfile.c.o
[37/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-version.c.o
[38/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-segstack.c.o
[39/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-init.c.o
[40/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-hash.c.o
[41/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-thread.c.o
[42/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-supervisor.c.o
[43/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-dbref.c.o
[44/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-gmp.c.o
[45/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-assert.c.o
[46/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-variant.c.o
[47/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-termhash.c.o
[48/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-codetable.c.o
[49/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-debug.c.o
[50/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-cont.c.o
[51/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-copyterm.c.o
[52/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-ressymbol.c.o
[53/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-indirect.c.o
[54/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-rsort.c.o
[55/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-dict.c.o
[56/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-mutex.c.o
[57/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-wrap.c.o
[58/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-allocpool.c.o
[59/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-event.c.o
[60/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-undo.c.o
[61/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-trie.c.o
[62/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-transaction.c.o
[63/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-coverage.c.o
[64/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-alloc.c.o
[65/555] Building C object src/CMakeFiles/swiplobjs.dir/os/pl-ctype.c.o
[66/555] Building C object src/CMakeFiles/swiplobjs.dir/os/pl-buffer.c.o
[67/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-index.c.o
[68/555] Building C object src/CMakeFiles/swiplobjs.dir/os/pl-files.c.o
[69/555] Building C object src/CMakeFiles/swiplobjs.dir/os/pl-glob.c.o
[70/555] Building C object src/CMakeFiles/swiplobjs.dir/os/pl-string.c.o
[71/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-fli.c.o
[72/555] Building C object src/CMakeFiles/swiplobjs.dir/os/pl-os.c.o
[73/555] Building C object src/CMakeFiles/swiplobjs.dir/pl-tabling.c.o
[74/555] Building C object src/CMakeFiles/swiplobjs.dir/os/pl-table.c.o
[75/555] Building C object src/CMakeFiles/swiplobjs.dir/os/pl-text.c.o
[76/555] Building C object src/CMakeFiles/swiplobjs.dir/os/pl-file.c.o
[77/555] Building C object src/CMakeFiles/swiplobjs.dir/os/pl-option.c.o
[78/555] Building C object src/CMakeFiles/swiplobjs.dir/os/pl-stream.c.o
[79/555] Building C object src/CMakeFiles/swiplobjs.dir/os/pl-fmt.c.o
[80/555] Building C object src/CMakeFiles/swiplobjs.dir/os/pl-codelist.c.o
[81/555] Building C object src/CMakeFiles/swiplobjs.dir/libtai/caltime_tai.c.o
[82/555] Building C object src/CMakeFiles/swiplobjs.dir/os/pl-cstack.c.o
[83/555] Building C object src/CMakeFiles/swiplobjs.dir/os/pl-dtoa.c.o
[84/555] Building C object src/CMakeFiles/swiplobjs.dir/libtai/leapsecs_sub.c.o
[85/555] Building C object src/CMakeFiles/swiplobjs.dir/libtai/leapsecs_add.c.o
[86/555] Building C object src/CMakeFiles/swiplobjs.dir/libtai/caldate_mjd.c.o
[87/555] Building C object src/CMakeFiles/swiplobjs.dir/os/pl-locale.c.o
[88/555] Building C object src/CMakeFiles/swiplobjs.dir/libtai/caldate_fmjd.c.o
[89/555] Building C object src/CMakeFiles/swiplobjs.dir/libtai/leapsecs_init.c.o
[90/555] Building C object src/CMakeFiles/swiplobjs.dir/libtai/tai_unpack.c.o
[91/555] Building C object src/CMakeFiles/swiplobjs.dir/libtai/tai_pack.c.o
[92/555] Building C object src/CMakeFiles/swiplobjs.dir/os/pl-tai.c.o
[93/555] Building C object src/CMakeFiles/swiplobjs.dir/libtai/leapsecs_read.c.o
[94/555] Building C object src/CMakeFiles/swiplobjs.dir/minizip/ioapi.c.o
[95/555] Building C object packages/sgml/CMakeFiles/plugin_sgml2pl.dir/xml_unicode.c.o
[96/555] Building C object src/CMakeFiles/swiplobjs.dir/os/pl-prologflag.c.o
[97/555] Building C object packages/tipc/CMakeFiles/plugin_tipc.dir/__/clib/nonblockio.c.o
[98/555] Building C object packages/sgml/CMakeFiles/plugin_sgml2pl.dir/quote.c.o
[99/555] Building C object src/CMakeFiles/swiplobjs.dir/minizip/zip.c.o
[100/555] Building C object src/CMakeFiles/swiplobjs.dir/minizip/unzip.c.o
[101/555] Building C object packages/clib/CMakeFiles/plugin_memfile.dir/error.c.o
[102/555] Building C object packages/sgml/CMakeFiles/plugin_sgml2pl.dir/xsd.c.o
[103/555] Building C object packages/http/CMakeFiles/plugin_http_stream.dir/http_stream.c.o
[104/555] Building C object packages/clib/CMakeFiles/plugin_streaminfo.dir/streaminfo.c.o
[105/555] Building C object packages/clib/CMakeFiles/plugin_streaminfo.dir/error.c.o
[106/555] Building C object packages/clib/CMakeFiles/plugin_memfile.dir/memfile.c.o
[107/555] Building C object packages/clib/CMakeFiles/plugin_prolog_stream.dir/prolog_stream.c.o
[108/555] Linking C shared module packages/clib/streaminfo.so
[109/555] Linking C shared module packages/clib/prolog_stream.so
[110/555] Building C object packages/clib/CMakeFiles/plugin_crypt.dir/error.c.o
[111/555] Building C object packages/sgml/CMakeFiles/plugin_sgml2pl.dir/sgml2pl.c.o
[112/555] Linking C shared module packages/clib/memfile.so
[113/555] Building C object packages/clib/CMakeFiles/plugin_crypt.dir/md5.c.o
[114/555] Building C object packages/clib/CMakeFiles/plugin_crypt.dir/crypt.c.o
[115/555] Building C object packages/clib/CMakeFiles/plugin_crypt.dir/md5passwd.c.o
[116/555] Building C object packages/clib/CMakeFiles/plugin_process.dir/error.c.o
[117/555] Building C object packages/clib/CMakeFiles/plugin_time.dir/error.c.o
[118/555] Linking C shared module packages/clib/crypt.so
[119/555] Building C object packages/clib/CMakeFiles/plugin_time.dir/time.c.o
[120/555] Building C object packages/clib/CMakeFiles/plugin_process.dir/process.c.o
[121/555] Linking C shared module packages/clib/time.so
[122/555] Building C object packages/clib/CMakeFiles/plugin_cgi.dir/cgi.c.o
[123/555] Building C object packages/clib/CMakeFiles/plugin_cgi.dir/error.c.o
[124/555] Linking C shared module packages/clib/process.so
[125/555] Building C object packages/clib/CMakeFiles/plugin_rlimit.dir/rlimit.c.o
[126/555] Building C object packages/clib/CMakeFiles/plugin_cgi.dir/form.c.o
[127/555] Building C object packages/clib/CMakeFiles/plugin_rlimit.dir/error.c.o
[128/555] Building C object packages/clib/CMakeFiles/plugin_sha4pl.dir/sha4pl.c.o
[129/555] Building C object packages/clib/CMakeFiles/plugin_sha4pl.dir/error.c.o
[130/555] Linking C shared module packages/clib/cgi.so
[131/555] Linking C shared module packages/clib/rlimit.so
[132/555] Building C object packages/clib/CMakeFiles/plugin_sha4pl.dir/sha1/hmac_sha1.c.o
[133/555] Building C object packages/clib/CMakeFiles/plugin_sha4pl.dir/sha1/hmac_sha256.c.o
[134/555] Building C object packages/clib/CMakeFiles/plugin_sha4pl.dir/sha1/sha1.c.o
[135/555] Linking C shared library src/libswipl.so.8.5.12
[136/555] Building C object packages/clib/CMakeFiles/plugin_files.dir/error.c.o
[137/555] Creating library symlink src/libswipl.so.8 src/libswipl.so
[138/555] Building C object packages/clib/CMakeFiles/plugin_sha4pl.dir/sha1/sha2.c.o
[139/555] Building C object packages/clib/CMakeFiles/plugin_files.dir/files.c.o
[140/555] Building C object packages/clib/CMakeFiles/plugin_mallocinfo.dir/error.c.o
[141/555] Building C object packages/clib/CMakeFiles/plugin_mallocinfo.dir/mallocinfo.c.o
[142/555] Linking C shared module packages/clib/sha4pl.so
[143/555] Linking C shared module packages/clib/files.so
[144/555] Building C object packages/clib/CMakeFiles/plugin_syslog.dir/syslog.c.o
[145/555] Linking C shared module packages/clib/mallocinfo.so
[146/555] Linking C executable src/swipl
[147/555] Building C object packages/clib/CMakeFiles/plugin_md54pl.dir/md54pl.c.o
[148/555] Linking C shared module packages/clib/syslog.so
[149/555] Building C object packages/clib/CMakeFiles/plugin_md54pl.dir/md5.c.o
[150/555] Building C object packages/clib/CMakeFiles/plugin_unix.dir/error.c.o
[151/555] Building C object packages/clib/CMakeFiles/plugin_uri.dir/uri.c.o
[152/555] Linking C shared module packages/clib/md54pl.so
[153/555] Building C object packages/clib/CMakeFiles/plugin_socket.dir/error.c.o
[154/555] Linking C shared module packages/clib/uri.so
[155/555] Building C object packages/clib/CMakeFiles/plugin_uuid.dir/uuid.c.o
[156/555] Building C object packages/clib/CMakeFiles/plugin_unix.dir/unix.c.o
[157/555] Building C object packages/clib/CMakeFiles/plugin_hashstream.dir/hash_stream.c.o
[158/555] Linking C shared module packages/clib/uuid.so
[159/555] Linking C shared module packages/clib/unix.so
[160/555] Building C object packages/clib/CMakeFiles/plugin_socket.dir/nonblockio.c.o
[161/555] Building C object packages/clib/CMakeFiles/plugin_socket.dir/socket.c.o
[162/555] Building C object packages/clib/CMakeFiles/plugin_hashstream.dir/md5.c.o
[163/555] Building C object packages/clib/CMakeFiles/plugin_uid.dir/error.c.o
[164/555] Linking C shared module packages/clib/socket.so
[165/555] Building C object packages/clib/CMakeFiles/plugin_hashstream.dir/sha1/sha1.c.o
[166/555] Building C object packages/clib/CMakeFiles/plugin_uid.dir/uid.c.o
[167/555] Building C object packages/clib/CMakeFiles/plugin_readutil.dir/readutil.c.o
[168/555] Linking C shared module packages/clib/uid.so
[169/555] Building C object packages/clib/CMakeFiles/plugin_hashstream.dir/sha1/sha2.c.o
[170/555] Linking C shared module packages/clib/readutil.so
[171/555] Building C object packages/cpp/CMakeFiles/plugin_ffi4pl.dir/ffi4pl.c.o
[172/555] Linking C shared module packages/clib/hashstream.so
[173/555] Linking C shared module packages/cpp/ffi4pl.so
[174/555] Building C object packages/inclpr/CMakeFiles/plugin_inclpr.dir/inclpr.c.o
[175/555] Linking C shared module packages/inclpr/inclpr.so
[176/555] Building C object packages/http/CMakeFiles/plugin_json.dir/json.c.o
[177/555] Linking C shared module packages/http/json.so
[178/555] Building C object packages/http/CMakeFiles/plugin_websocket.dir/websocket.c.o
[179/555] Linking C shared module packages/http/http_stream.so
[180/555] Linking C shared module packages/http/websocket.so
[181/555] Building C object packages/tipc/CMakeFiles/plugin_tipc.dir/__/clib/error.c.o
[182/555] Building C object packages/ltx2htm/CMakeFiles/plugin_tex.dir/psfile.c.o
[183/555] Building C object packages/nlp/CMakeFiles/plugin_snowball.dir/snowball.c.o
[184/555] Building C object packages/tipc/CMakeFiles/plugin_tipc.dir/tipc.c.o
[185/555] Building C object packages/nlp/CMakeFiles/plugin_double_metaphone.dir/double_metaphone.c.o
[186/555] Linking C shared module packages/nlp/double_metaphone.so
[187/555] Linking C shared module packages/tipc/tipc.so
[188/555] Building C object packages/ltx2htm/CMakeFiles/plugin_tex.dir/tex.c.o
[189/555] Building C object packages/nlp/CMakeFiles/plugin_porter_stem.dir/porter_stem.c.o
[190/555] Building C object packages/nlp/CMakeFiles/plugin_isub.dir/pl-isub.c.o
[191/555] Building C object packages/nlp/CMakeFiles/plugin_isub.dir/isub.c.o
[192/555] Linking C shared module packages/ltx2htm/tex.so
[193/555] Linking C shared module packages/nlp/porter_stem.so
[194/555] Linking C shared module packages/nlp/isub.so
[195/555] Building C object packages/nlp/libstemmer_c/CMakeFiles/libstemmer.dir/src_c/stem_UTF_8_danish.c.o
[196/555] Building C object packages/nlp/libstemmer_c/CMakeFiles/libstemmer.dir/src_c/stem_UTF_8_dutch.c.o
[197/555] Building C object packages/odbc/CMakeFiles/plugin_odbc4pl.dir/odbc.c.o
[198/555] Generating ../home/boot.prc
[199/555] Building C object packages/nlp/libstemmer_c/CMakeFiles/libstemmer.dir/src_c/stem_UTF_8_english.c.o
[200/555] Building C object packages/nlp/libstemmer_c/CMakeFiles/libstemmer.dir/src_c/stem_UTF_8_finnish.c.o
[201/555] Build home/library/INDEX.pl
[202/555] Building C object packages/nlp/libstemmer_c/CMakeFiles/libstemmer.dir/src_c/stem_UTF_8_hungarian.c.o
[203/555] Building C object packages/nlp/libstemmer_c/CMakeFiles/libstemmer.dir/src_c/stem_UTF_8_german.c.o
[204/555] Building C object packages/nlp/libstemmer_c/CMakeFiles/libstemmer.dir/src_c/stem_UTF_8_french.c.o
[205/555] Build home/library/dcg/INDEX.pl
[206/555] Build home/library/lynx/INDEX.pl
[207/555] Build home/library/cql/INDEX.pl
[208/555] Build home/library/http/INDEX.pl
[209/555] Build home/library/clp/INDEX.pl
[210/555] Build home/library/tipc/INDEX.pl
[211/555] Build home/library/unicode/INDEX.pl
[212/555] Building C object packages/nlp/libstemmer_c/CMakeFiles/libstemmer.dir/src_c/stem_UTF_8_norwegian.c.o
[213/555] Building C object packages/nlp/libstemmer_c/CMakeFiles/libstemmer.dir/src_c/stem_UTF_8_italian.c.o
[214/555] Building C object packages/nlp/libstemmer_c/CMakeFiles/libstemmer.dir/src_c/stem_UTF_8_russian.c.o
[215/555] Building C object packages/nlp/libstemmer_c/CMakeFiles/libstemmer.dir/src_c/stem_UTF_8_romanian.c.o
[216/555] Building C object packages/nlp/libstemmer_c/CMakeFiles/libstemmer.dir/src_c/stem_UTF_8_swedish.c.o
[217/555] Building C object packages/nlp/libstemmer_c/CMakeFiles/libstemmer.dir/src_c/stem_UTF_8_porter.c.o
[218/555] Building C object packages/nlp/libstemmer_c/CMakeFiles/libstemmer.dir/src_c/stem_UTF_8_spanish.c.o
[219/555] Building C object packages/nlp/libstemmer_c/CMakeFiles/libstemmer.dir/src_c/stem_UTF_8_portuguese.c.o
[220/555] Building C object packages/nlp/libstemmer_c/CMakeFiles/libstemmer.dir/runtime/api.c.o
[221/555] Building C object packages/nlp/libstemmer_c/CMakeFiles/libstemmer.dir/libstemmer/libstemmer_utf8.c.o
[222/555] Building C object packages/nlp/libstemmer_c/CMakeFiles/libstemmer.dir/runtime/utilities.c.o
[223/555] Build home/library/protobufs/gen_pb/google/protobuf/compiler/INDEX.pl
[224/555] Building C object packages/PDT/CMakeFiles/plugin_pdt_console.dir/pdt_console.c.o
[225/555] Building C object packages/protobufs/CMakeFiles/plugin_protobufs.dir/protobufs.c.o
[226/555] Linking C shared module packages/PDT/pdt_console.so
[227/555] Building C object packages/nlp/libstemmer_c/CMakeFiles/libstemmer.dir/src_c/stem_UTF_8_turkish.c.o
[228/555] Linking C shared module packages/protobufs/protobufs.so
[229/555] Building C object packages/redis/CMakeFiles/plugin_redis4pl.dir/redis4pl.c.o
[230/555] Build home/library/protobufs/gen_pb/google/protobuf/INDEX.pl
[231/555] Linking C static library packages/nlp/libstemmer_c/liblibstemmer.a
[232/555] Linking C shared module packages/redis/redis4pl.so
[233/555] Linking C shared module packages/nlp/snowball.so
[234/555] Building C object packages/semweb/CMakeFiles/plugin_rdf_db.dir/md5.c.o
[235/555] Building C object packages/semweb/CMakeFiles/plugin_rdf_db.dir/atom.c.o
[236/555] Building C object packages/semweb/CMakeFiles/plugin_rdf_db.dir/debug.c.o
[237/555] Building C object packages/semweb/CMakeFiles/plugin_rdf_db.dir/murmur.c.o
[238/555] Building C object packages/semweb/CMakeFiles/plugin_rdf_db.dir/hash.c.o
[239/555] Building C object packages/semweb/CMakeFiles/plugin_rdf_db.dir/atom_map.c.o
[240/555] Building C object packages/semweb/CMakeFiles/plugin_rdf_db.dir/resource.c.o
[241/555] Building C object packages/semweb/CMakeFiles/plugin_rdf_db.dir/error.c.o
[242/555] Building C object packages/semweb/CMakeFiles/plugin_rdf_db.dir/skiplist.c.o
[243/555] Building C object packages/semweb/CMakeFiles/plugin_rdf_db.dir/snapshot.c.o
[244/555] Building C object packages/semweb/CMakeFiles/plugin_rdf_db.dir/query.c.o
[245/555] Building C object packages/semweb/CMakeFiles/plugin_rdf_db.dir/xsd.c.o
[246/555] Building C object packages/semweb/CMakeFiles/plugin_turtle.dir/murmur.c.o
[247/555] Building C object packages/sgml/CMakeFiles/plugin_sgml2pl.dir/model.c.o
[248/555] Build home/library/semweb/INDEX.pl
[249/555] Building C object packages/semweb/CMakeFiles/plugin_ntriples.dir/ntriples.c.o
[250/555] Building C object packages/sgml/CMakeFiles/plugin_sgml2pl.dir/xmlns.c.o
[251/555] Linking C shared module packages/semweb/ntriples.so
[252/555] Building C object packages/sgml/CMakeFiles/plugin_sgml2pl.dir/error.c.o
[253/555] Building C object packages/table/CMakeFiles/plugin_table.dir/error.c.o
[254/555] Linking C shared module packages/sgml/sgml2pl.so
[255/555] Building C object packages/table/CMakeFiles/plugin_table.dir/order.c.o
[256/555] Building C object packages/semweb/CMakeFiles/plugin_turtle.dir/turtle.c.o
[257/555] Building C object packages/table/CMakeFiles/plugin_table.dir/table.c.o
[258/555] Building C object packages/utf8proc/CMakeFiles/plugin_unicode4pl.dir/unicode4pl.c.o
[259/555] Linking C shared module packages/semweb/turtle.so
[260/555] Linking C shared module packages/table/table.so
[261/555] Linking C shared module packages/odbc/odbc4pl.so
[262/555] Building C object packages/zlib/CMakeFiles/plugin_zlib4pl.dir/zlib4pl.c.o
[263/555] Linking C shared module packages/zlib/zlib4pl.so
[264/555] Building C object packages/utf8proc/CMakeFiles/plugin_unicode4pl.dir/utf8proc.c.o
[265/555] Building C object packages/semweb/CMakeFiles/plugin_rdf_db.dir/rdf_db.c.o
[266/555] Linking C shared module packages/utf8proc/unicode4pl.so
[267/555] Building C object packages/archive/CMakeFiles/plugin_archive4pl.dir/archive4pl.c.o
[268/555] Building C object packages/yaml/CMakeFiles/plugin_yaml4pl.dir/yaml4pl.c.o
[269/555] Linking C shared module packages/semweb/rdf_db.so
[270/555] Linking C shared module packages/archive/archive4pl.so
[271/555] Linking C shared module packages/yaml/yaml4pl.so
[272/555] Building C object packages/ssl/CMakeFiles/plugin_crypto4pl.dir/__/clib/error.c.o
[273/555] Building C object packages/bdb/CMakeFiles/plugin_bdb4pl.dir/bdb4pl.c.o
[274/555] Building C object packages/ssl/CMakeFiles/plugin_crypto4pl.dir/crypto4pl.c.o
[275/555] Building C object packages/pcre/CMakeFiles/plugin_pcre4pl.dir/pcre4pl.c.o
[276/555] Linking C shared module packages/bdb/bdb4pl.so
[277/555] Linking C shared module packages/pcre/pcre4pl.so
[278/555] Linking C shared module packages/ssl/crypto4pl.so
[279/555] Automatic MOC and UIC for target swipl-win
[280/555] Building C object packages/ssl/CMakeFiles/plugin_ssl4pl.dir/__/clib/error.c.o
[281/555] Building C object packages/xpce/CMakeFiles/find_names.dir/src/find_names.c.o
[282/555] Building C object packages/ssl/CMakeFiles/plugin_ssl4pl.dir/ssl4pl.c.o
[283/555] Building C object packages/jpl/CMakeFiles/plugin_libjpl.dir/src/main/c/jpl.c.o
[284/555] Linking C shared module packages/jpl/libjpl.so
[285/555] Linking C shared module packages/ssl/ssl4pl.so
[286/555] Building CXX object packages/swipl-win/CMakeFiles/swipl-win.dir/main.cpp.o
[287/555] Building CXX object packages/swipl-win/CMakeFiles/swipl-win.dir/swipl-win_autogen/mocs_compilation.cpp.o
[288/555] Building CXX object packages/swipl-win/CMakeFiles/swipl-win.dir/Preferences.cpp.o
[289/555] Building CXX object packages/swipl-win/CMakeFiles/swipl-win.dir/SwiPrologEngine.cpp.o
[290/555] Building CXX object packages/swipl-win/CMakeFiles/swipl-win.dir/Swipl_IO.cpp.o
[291/555] Building CXX object packages/swipl-win/CMakeFiles/swipl-win.dir/pqMainWindow.cpp.o
[292/555] Building CXX object packages/swipl-win/CMakeFiles/swipl-win.dir/pqConsole.cpp.o
[293/555] Building CXX object packages/swipl-win/CMakeFiles/swipl-win.dir/ConsoleEdit.cpp.o
[294/555] Building CXX object packages/swipl-win/CMakeFiles/swipl-win.dir/Completion.cpp.o
[295/555] Building CXX object packages/swipl-win/CMakeFiles/swipl-win.dir/qrc_swipl-win.cpp.o
[296/555] Linking C executable packages/xpce/find_names
[297/555] Building CXX object packages/swipl-win/CMakeFiles/swipl-win.dir/swipl_win.cpp.o
[298/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/adt/area.c.o
[299/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/adt/bool.c.o
[300/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/adt/atable.c.o
[301/555] Building CXX object packages/swipl-win/CMakeFiles/swipl-win.dir/FlushOutputEvents.cpp.o
[302/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/adt/attribute.c.o
[303/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/adt/chaintable.c.o
[304/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/adt/date.c.o
[305/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/adt/chain.c.o
[306/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/adt/constant.c.o
[307/555] Building CXX object packages/swipl-win/CMakeFiles/swipl-win.dir/ParenMatching.cpp.o
[308/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/adt/number.c.o
[309/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/adt/dict.c.o
[310/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/adt/dictitem.c.o
[311/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/adt/point.c.o
[312/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/adt/hashtable.c.o
[313/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/adt/real.c.o
[314/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/adt/region.c.o
[315/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/adt/tuple.c.o
[316/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/adt/sheet.c.o
[317/555] Building CXX object packages/swipl-win/CMakeFiles/swipl-win.dir/ansi_esc_seq.cpp.o
[318/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/adt/size.c.o
[319/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/adt/vector.c.o
[320/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ari/equation.c.o
[321/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ari/expression.c.o
[322/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/evt/clickgesture.c.o
[323/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/evt/conngesture.c.o
[324/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/evt/gesture.c.o
[325/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/evt/event.c.o
[326/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/evt/eventnode.c.o
[327/555] Linking CXX executable packages/swipl-win/swipl-win
/usr/bin/ld: /lib/x86_64-linux-gnu/libasan.so.5: warning: the use of `tmpnam' is dangerous, better use `mkstemp'
/usr/bin/ld: /lib/x86_64-linux-gnu/libasan.so.5: warning: the use of `tempnam' is dangerous, better use `mkstemp'
/usr/bin/ld: /lib/x86_64-linux-gnu/libasan.so.5: warning: the use of `tmpnam_r' is dangerous, better use `mkstemp'
[328/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/evt/eventtree.c.o
[329/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gnu/getdate.c.o
[330/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/evt/handler.c.o
[331/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/evt/handlergroup.c.o
[332/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/evt/modifier.c.o
[333/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/evt/mvolgesture.c.o
[334/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/evt/movegesture.c.o
[335/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/evt/popupgesture.c.o
[336/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/evt/recogniser.c.o
[337/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/evt/edittextgest.c.o
[338/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/evt/resizegesture.c.o
[339/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/evt/rzolgesture.c.o
[340/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/evt/browserselgesture.c.o
[341/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/evt/resizetabslice.c.o
[342/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/arrow.c.o
[343/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/arc.c.o
[344/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/box.c.o
[345/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/circle.c.o
[346/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/bitmap.c.o
[347/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/cursor.c.o
[348/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/ellipse.c.o
[349/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/connection.c.o
[350/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/colour.c.o
[351/555] Generating pldoc2tex
[352/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/figure.c.o
[353/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/format.c.o
[354/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/handle.c.o
[355/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/joint.c.o
[356/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/font.c.o
[357/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/link.c.o
[358/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/line.c.o
[359/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/device.c.o
[360/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/image.c.o
[361/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/node.c.o
[362/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/graphical.c.o
[363/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/path.c.o
[364/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/postscript.c.o
[365/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/listbrowser.c.o
[366/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/scrollbar.c.o
[367/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/visual.c.o
[368/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/pixmap.c.o
[369/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/tree.c.o
[370/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/text.c.o
[371/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/pen.c.o
[372/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/elevation.c.o
[373/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/draw.c.o
[374/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/colourmap.c.o
[375/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/hsv.c.o
[376/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/gra/bezier.c.o
[377/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/itf/asfile.c.o
[378/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/itf/cpointer.c.o
[379/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/itf/console.c.o
[380/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/itf/host.c.o
[381/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/itf/stub.c.o
[382/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/itf/c.c.o
[383/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/itf/xmalloc.c.o
[384/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/itf/srcsink.c.o
[385/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/itf/interface.c.o
[386/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/itf/hostdata.c.o
[387/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/itf/public.c.o
[388/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/itf/iostream.c.o
[389/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/itf/rc.c.o
[390/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/alloc.c.o
[391/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/assoc.c.o
[392/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/behaviour.c.o
[393/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/error.c.o
[394/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/debug.c.o
[395/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/gc.c.o
[396/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/declarations.c.o
[397/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/getmethod.c.o
[398/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/glob.c.o
[399/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/conversion.c.o
[400/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/global.c.o
[401/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/method.c.o
[402/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/name.c.o
[403/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/programobject.c.o
[404/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/goodies.c.o
[405/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/class.c.o
[406/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/passing.c.o
[407/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/timer.c.o
[408/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/save.c.o
[409/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/object.c.o
[410/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/srclocation.c.o
[411/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/sendmethod.c.o
[412/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/trace.c.o
[413/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/inline.c.o
[414/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/xref.c.o
[415/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/variable.c.o
[416/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/self.c.o
[417/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/men/button.c.o
[418/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/type.c.o
[419/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/ker/classvar.c.o
[420/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/men/label.c.o
[421/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/men/dialogitem.c.o
[422/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/men/menubar.c.o
[423/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/men/menuitem.c.o
[424/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/men/popup.c.o
[425/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/men/intitem.c.o
[426/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/men/slider.c.o
[427/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/men/tab.c.o
[428/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/men/tabstack.c.o
[429/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/men/menu.c.o
[430/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/men/diagroup.c.o
[431/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/men/textitem.c.o
[432/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/men/labelbox.c.o
[433/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/fmt/layoutmgr.c.o
[434/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/fmt/layoutitf.c.o
[435/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/box/hbox.c.o
[436/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/box/boxes.c.o
[437/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/fmt/tabcell.c.o
[438/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/box/rubber.c.o
[439/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/fmt/tabslice.c.o
[440/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/box/tbox.c.o
[441/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/box/lbox.c.o
[442/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/box/grbox.c.o
[443/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/msg/binding.c.o
[444/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/msg/and.c.o
[445/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/msg/assign.c.o
[446/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/fmt/table.c.o
[447/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/msg/block.c.o
[448/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/box/parbox.c.o
[449/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/msg/equal.c.o
[450/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/msg/create.c.o
[451/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/msg/code.c.o
[452/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/msg/obtain.c.o
[453/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/msg/if.c.o
[454/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/msg/function.c.o
[455/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/msg/not.c.o
[456/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/msg/nonequal.c.o
[457/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/msg/message.c.o
[458/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/msg/or.c.o
[459/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/msg/var.c.o
[460/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/msg/progn.c.o
[461/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/msg/quote.c.o
[462/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/msg/when.c.o
[463/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/msg/while.c.o
[464/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/msg/nameref.c.o
[465/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/prg/operator.c.o
[466/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/rel/hyper.c.o
[467/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/prg/parser.c.o
[468/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/rel/constraint.c.o
[469/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/rel/relation.c.o
[470/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/rel/identity.c.o
[471/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/rel/spatial.c.o
[472/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/rgx/regfree.c.o
[473/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/prg/tokeniser.c.o
[474/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/rgx/regerror.c.o
[475/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/txt/fragment.c.o
[476/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/rgx/regexecW.c.o
[477/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/txt/chararray.c.o
[478/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/txt/regex.c.o
[479/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/txt/style.c.o
[480/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/txt/keybinding.c.o
[481/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/txt/str.c.o
[482/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/txt/string.c.o
[483/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/txt/syntax.c.o
[484/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/txt/textcursor.c.o
[485/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/txt/undo.c.o
[486/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/txt/utf8.c.o
[487/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/txt/editor.c.o
[488/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/rgx/regcompW.c.o
[489/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/txt/textmargin.c.o
[490/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/txt/i18n.c.o
[491/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/unx/directory.c.o
[492/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/unx/file.c.o
[493/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/txt/textbuffer.c.o
[494/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/unx/process.c.o
[495/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/unx/stream.c.o
[496/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/unx/socket.c.o
[497/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/win/browser.c.o
[498/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/win/dialog.c.o
[499/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/txt/textimage.c.o
[500/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/win/decorate.c.o
[501/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/win/setup.c.o
[502/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/win/picture.c.o
[503/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/win/tileadjust.c.o
[504/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/win/displaymgr.c.o
[505/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/win/monitor.c.o
[506/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/win/display.c.o
[507/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/win/tile.c.o
[508/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/win/view.c.o
[509/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/img/jdatasrc.c.o
[510/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/img/jdatadst.c.o
[511/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/win/frame.c.o
[512/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/win/application.c.o
[513/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/img/gifread.c.o
[514/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/img/imgutil.c.o
[515/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/img/giftoxpm.c.o
[516/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/x11/canvas.c.o
[517/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/img/jpegtoxpm.c.o
[518/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/x11/fshell.c.o
[519/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/win/window.c.o
[520/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/img/gifwrite.c.o
[521/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/x11/x11-compat.c.o
[522/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/x11/xcommon.c.o
[523/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/x11/xcolour.c.o
[524/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/x11/xppm.c.o
[525/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/x11/xcursor.c.o
[526/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/x11/xconvert.c.o
[527/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/x11/xfont.c.o
[528/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/x11/xevent.c.o
[529/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/x11/xdisplay.c.o
[530/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/x11/xtimer.c.o
[531/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/x11/xstream.c.o
[532/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/x11/xwindow.c.o
[533/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/x11/x11.c.o
[534/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/x11/xframe.c.o
[535/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/x11/ximage.c.o
[536/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/x11/xunix.c.o
[537/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/x11/xdraw.c.o
[538/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/x11/xmenu.c.o
[539/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/x11/xdnd.c.o
[540/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/swipl/pcecall.c.o
[541/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/src/x11/xjpeg.c.o
[542/555] Building C object packages/readline/CMakeFiles/plugin_readline4pl.dir/readline4pl.c.o
[543/555] Linking C shared module packages/readline/readline4pl.so
[544/555] Building C object packages/libedit/CMakeFiles/plugin_libedit4pl.dir/libedit4pl.c.o
[545/555] Linking C shared module packages/libedit/libedit4pl.so
[546/555] Building C object packages/xpce/CMakeFiles/plugin_pl2xpce.dir/swipl/interface.c.o
[547/555] Linking C shared module packages/xpce/pl2xpce.so
[548/555] -- Building xpce predicate index
[549/555] Generating home/doc/manindex.db
[550/555] -- Building manual index
[551/555] -- Building xpce class index
[552/555] QLF compiling pce.qlf
[553/555] QLF compiling emacs/emacs.qlf
[554/555] QLF compiling trace/trace.qlf
[555/555] QLF compiling emacs/prolog_mode.qlf
UpdateCTestConfiguration from :/home/peter/src/swipl-devel/build.sanitize/DartConfiguration.tcl
UpdateCTestConfiguration from :/home/peter/src/swipl-devel/build.sanitize/DartConfiguration.tcl
Test project /home/peter/src/swipl-devel/build.sanitize
Constructing a list of tests
Done constructing a list of tests
Updating test list for fixtures
Added 0 tests to meet fixture requirements
Checking test dependency graph...
Checking test dependency graph end
test 71
Start 71: archive:archive
71: Test command: /home/peter/src/swipl-devel/build.sanitize/src/swipl "-p" "foreign=" "-f" "none" "--no-packs" "--on-error=status" "-s" "/home/peter/src/swipl-devel/packages/archive/test_archive.pl" "-g" "test_archive" "-t" "halt"
71: Test timeout computed to be: 10000000
71: Warning: /home/peter/src/swipl-devel/packages/archive/test_archive.pl:146:
71: Warning: Clauses of plunit_archive:zztest/2 are not together in the source-file
71: Warning: Earlier definition at /home/peter/src/swipl-devel/packages/archive/test_archive.pl:92
71: Warning: Current predicate: plunit_archive:'unit body'/2
71: Warning: Use :- discontiguous plunit_archive:zztest/2. to suppress this message
71:
71: ***ARCHIVE_OPEN '/tmp/swipl_714659_1' read <stream>(0x61100002f200)
71:
71: AR_W_ACQUIRE_CB 0x606000011840 0x61100002f200 (r) AR_VIRGIN close_parent=0 symbol=802949 archive=(nil) entry=(nil) agc=0
71: AR_ERROR 0x606000011840 0x61100002f200 (r) AR_VIRGIN close_parent=1 symbol=802949 archive=0x61d00003b680 entry=(nil) agc=0
71: % PL-Unit: archive
71: ***ARCHIVE_OPEN '/tmp/swipl_714659_2' read <stream>(0x61100002f480)
71:
71: AR_W_ACQUIRE_CB 0x606000012080 0x61100002f480 (r) AR_VIRGIN close_parent=0 symbol=804229 archive=(nil) entry=(nil) agc=0
71: ARCHIVE_CLOSE 0x606000012080 0x61100002f480 (r) AR_OPENED_ARCHIVE close_parent=1 symbol=804229 archive=0x61d00003c080 entry=(nil) agc=0
71: ARCHIVE_CLOSE_ 0x606000012080 0x61100002f480 (r) AR_OPENED_ARCHIVE close_parent=1 symbol=804229 archive=0x61d00003c080 entry=(nil) agc=0
71: .
71: ***ARCHIVE_OPEN '/dev/null' read <stream>(0x61100002f5c0)
71:
71: AR_W_ACQUIRE_CB 0x6060000121a0 0x61100002f5c0 (r) AR_VIRGIN close_parent=0 symbol=804485 archive=(nil) entry=(nil) agc=0
71: ARCHIVE_CLOSE 0x6060000121a0 0x61100002f5c0 (r) AR_OPENED_ARCHIVE close_parent=1 symbol=804485 archive=0x61d00003ca80 entry=(nil) agc=0
71: ARCHIVE_CLOSE_ 0x6060000121a0 0x61100002f5c0 (r) AR_OPENED_ARCHIVE close_parent=1 symbol=804485 archive=0x61d00003ca80 entry=(nil) agc=0
71: .
71: ***ARCHIVE_OPEN '/tmp/swipl_714659_3' write <stream>(0x61100002fac0)
71:
71: AR_W_ACQUIRE_CB 0x606000012560 0x61100002fac0 (w) AR_VIRGIN close_parent=0 symbol=809477 archive=(nil) entry=(nil) agc=0
71: ARCHIVE_NEXT_HEADER 0x606000012560 0x61100002fac0 (w) AR_OPENED_ARCHIVE close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: ARCHIVE_OPEN_ENTRY 0x606000012560 0x61100002fac0 (w) AR_NEW_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_CLOSE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: LIBARCHIVE_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_CLOSE_CB/2 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: ARCHIVE_NEXT_HEADER 0x606000012560 0x61100002fac0 (w) AR_OPENED_ARCHIVE close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: ARCHIVE_OPEN_ENTRY 0x606000012560 0x61100002fac0 (w) AR_NEW_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_CLOSE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: LIBARCHIVE_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_CLOSE_CB/2 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: ARCHIVE_NEXT_HEADER 0x606000012560 0x61100002fac0 (w) AR_OPENED_ARCHIVE close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: ARCHIVE_OPEN_ENTRY 0x606000012560 0x61100002fac0 (w) AR_NEW_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_CLOSE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: AR_ENTRY_CLOSE_CB/2 0x606000012560 0x61100002fac0 (w) AR_OPENED_ENTRY close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: ARCHIVE_CLOSE 0x606000012560 0x61100002fac0 (w) AR_OPENED_ARCHIVE close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: ARCHIVE_CLOSE_ 0x606000012560 0x61100002fac0 (w) AR_OPENED_ARCHIVE close_parent=1 symbol=809477 archive=0x61300002b540 entry=0x61a00000ba80 agc=0
71: LIBARCHIVE_WRITE_CB 0x606000012560 0x61100002fac0 (w) AR_OPENED_ARCHIVE close_parent=1 symbol=809477 archive=(nil) entry=0x61a00000ba80 agc=0
71:
71: ***ARCHIVE_OPEN '/tmp/swipl_714659_3' read <stream>(0x61100000e500)
71:
71: AR_W_ACQUIRE_CB 0x606000012680 0x61100000e500 (r) AR_VIRGIN close_parent=0 symbol=811781 archive=(nil) entry=(nil) agc=0
71: ARCHIVE_NEXT_HEADER 0x606000012680 0x61100000e500 (r) AR_OPENED_ARCHIVE close_parent=1 symbol=811781 archive=0x61d00003d480 entry=(nil) agc=0
71: ARCHIVE_NEXT_HEADER 0x606000012680 0x61100000e500 (r) AR_NEW_ENTRY close_parent=1 symbol=811781 archive=0x61d00003d480 entry=0x61a00000d280 agc=0
71: LIBARCHIVE_SKIP_CB 0x606000012680 0x61100000e500 (r) AR_NEW_ENTRY close_parent=1 symbol=811781 archive=0x61d00003d480 entry=(nil) agc=0
71: ARCHIVE_NEXT_HEADER 0x606000012680 0x61100000e500 (r) AR_NEW_ENTRY close_parent=1 symbol=811781 archive=0x61d00003d480 entry=0x61a00000d280 agc=0
71: LIBARCHIVE_SKIP_CB 0x606000012680 0x61100000e500 (r) AR_NEW_ENTRY close_parent=1 symbol=811781 archive=0x61d00003d480 entry=(nil) agc=0
71: ARCHIVE_NEXT_HEADER 0x606000012680 0x61100000e500 (r) AR_NEW_ENTRY close_parent=1 symbol=811781 archive=0x61d00003d480 entry=0x61a00000d280 agc=0
71: ARCHIVE_CLOSE 0x606000012680 0x61100000e500 (r) AR_OPENED_ARCHIVE close_parent=1 symbol=811781 archive=0x61d00003d480 entry=0x61a00000d280 agc=0
71: ARCHIVE_CLOSE_ 0x606000012680 0x61100000e500 (r) AR_OPENED_ARCHIVE close_parent=1 symbol=811781 archive=0x61d00003d480 entry=0x61a00000d280 agc=0
71: .
71: ***ARCHIVE_OPEN '/tmp/swipl_714659_4' write <stream>(0x61100000e780)
71:
71: AR_W_ACQUIRE_CB 0x606000012800 0x61100000e780 (w) AR_VIRGIN close_parent=0 symbol=812293 archive=(nil) entry=(nil) agc=0
71: ARCHIVE_NEXT_HEADER 0x606000012800 0x61100000e780 (w) AR_OPENED_ARCHIVE close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: ARCHIVE_OPEN_ENTRY 0x606000012800 0x61100000e780 (w) AR_NEW_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_CLOSE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: LIBARCHIVE_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_CLOSE_CB/2 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: ARCHIVE_NEXT_HEADER 0x606000012800 0x61100000e780 (w) AR_OPENED_ARCHIVE close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: ARCHIVE_OPEN_ENTRY 0x606000012800 0x61100000e780 (w) AR_NEW_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_CLOSE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: LIBARCHIVE_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_CLOSE_CB/2 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: ARCHIVE_NEXT_HEADER 0x606000012800 0x61100000e780 (w) AR_OPENED_ARCHIVE close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: ARCHIVE_OPEN_ENTRY 0x606000012800 0x61100000e780 (w) AR_NEW_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_CLOSE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: AR_ENTRY_CLOSE_CB/2 0x606000012800 0x61100000e780 (w) AR_OPENED_ENTRY close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: ARCHIVE_CLOSE 0x606000012800 0x61100000e780 (w) AR_OPENED_ARCHIVE close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: ARCHIVE_CLOSE_ 0x606000012800 0x61100000e780 (w) AR_OPENED_ARCHIVE close_parent=1 symbol=812293 archive=0x61300002b700 entry=0x61a00000d880 agc=0
71: LIBARCHIVE_WRITE_CB 0x606000012800 0x61100000e780 (w) AR_OPENED_ARCHIVE close_parent=1 symbol=812293 archive=(nil) entry=0x61a00000d880 agc=0
71:
71: ***ARCHIVE_OPEN '/tmp/swipl_714659_4' read <stream>(0x61100000f180)
71:
71: AR_W_ACQUIRE_CB 0x606000012860 0x61100000f180 (r) AR_VIRGIN close_parent=0 symbol=813445 archive=(nil) entry=(nil) agc=0
71: ARCHIVE_NEXT_HEADER 0x606000012860 0x61100000f180 (r) AR_OPENED_ARCHIVE close_parent=1 symbol=813445 archive=0x61d00003e880 entry=(nil) agc=0
71: LIBARCHIVE_SKIP_CB 0x606000012860 0x61100000f180 (r) AR_OPENED_ARCHIVE close_parent=1 symbol=813445 archive=0x61d00003e880 entry=(nil) agc=0
71: ARCHIVE_OPEN_ENTRY 0x606000012860 0x61100000f180 (r) AR_NEW_ENTRY close_parent=1 symbol=813445 archive=0x61d00003e880 entry=0x61a00000f080 agc=0
71: ARCHIVE_CLOSE 0x606000012860 0x61100000f180 (r) AR_OPENED_ENTRY close_parent=1 symbol=813445 archive=0x61d00003e880 entry=0x61a00000f080 agc=0
71: ARCHIVE_CLOSE_ 0x606000012860 0x61100000f180 (r) AR_OPENED_ENTRY close_parent=1 symbol=813445 archive=0x61d00003e880 entry=0x61a00000f080 agc=0
71: AR_ENTRY_READ_CB 0x606000012860 0x61100000f180 (r) AR_OPENED_ENTRY_PENDING_CLOSE close_parent=1 symbol=813445 archive=0x61d00003e880 entry=0x61a00000f080 agc=0
71: AR_ENTRY_READ_CB 0x606000012860 0x61100000f180 (r) AR_OPENED_ENTRY_PENDING_CLOSE close_parent=1 symbol=813445 archive=0x61d00003e880 entry=0x61a00000f080 agc=0
71: AR_ENTRY_READ_CB 0x606000012860 0x61100000f180 (r) AR_OPENED_ENTRY_PENDING_CLOSE close_parent=1 symbol=813445 archive=0x61d00003e880 entry=0x61a00000f080 agc=0
71: AR_ENTRY_READ_CB 0x606000012860 0x61100000f180 (r) AR_OPENED_ENTRY_PENDING_CLOSE close_parent=1 symbol=813445 archive=0x61d00003e880 entry=0x61a00000f080 agc=0
71: AR_ENTRY_READ_CB 0x606000012860 0x61100000f180 (r) AR_OPENED_ENTRY_PENDING_CLOSE close_parent=1 symbol=813445 archive=0x61d00003e880 entry=0x61a00000f080 agc=0
71: AR_ENTRY_READ_CB 0x606000012860 0x61100000f180 (r) AR_OPENED_ENTRY_PENDING_CLOSE close_parent=1 symbol=813445 archive=0x61d00003e880 entry=0x61a00000f080 agc=0
71: AR_ENTRY_READ_CB 0x606000012860 0x61100000f180 (r) AR_OPENED_ENTRY_PENDING_CLOSE close_parent=1 symbol=813445 archive=0x61d00003e880 entry=0x61a00000f080 agc=0
71: AR_ENTRY_READ_CB 0x606000012860 0x61100000f180 (r) AR_OPENED_ENTRY_PENDING_CLOSE close_parent=1 symbol=813445 archive=0x61d00003e880 entry=0x61a00000f080 agc=0
71: AR_ENTRY_CLOSE_CB 0x606000012860 0x61100000f180 (r) AR_OPENED_ENTRY_PENDING_CLOSE close_parent=1 symbol=813445 archive=0x61d00003e880 entry=0x61a00000f080 agc=0
71: ARCHIVE_CLOSE_ 0x606000012860 0x61100000f180 (r) AR_OPENED_ARCHIVE close_parent=1 symbol=813445 archive=0x61d00003e880 entry=0x61a00000f080 agc=0
71: AR_ENTRY_CLOSE_CB/2 0x606000012860 (nil) (r) AR_VIRGIN close_parent=1 symbol=813445 archive=(nil) entry=(nil) agc=0
71: .
71: ***ARCHIVE_OPEN '/tmp/swipl_714659_5' write <stream>(0x61100000f540)
71:
71: AR_W_ACQUIRE_CB 0x6060000129e0 0x61100000f540 (w) AR_VIRGIN close_parent=0 symbol=814085 archive=(nil) entry=(nil) agc=0
71: ARCHIVE_NEXT_HEADER 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ARCHIVE close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: ARCHIVE_OPEN_ENTRY 0x6060000129e0 0x61100000f540 (w) AR_NEW_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_CLOSE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: LIBARCHIVE_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_CLOSE_CB/2 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: ARCHIVE_NEXT_HEADER 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ARCHIVE close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: ARCHIVE_OPEN_ENTRY 0x6060000129e0 0x61100000f540 (w) AR_NEW_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_CLOSE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: LIBARCHIVE_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_CLOSE_CB/2 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: ARCHIVE_NEXT_HEADER 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ARCHIVE close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: ARCHIVE_OPEN_ENTRY 0x6060000129e0 0x61100000f540 (w) AR_NEW_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_CLOSE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: AR_ENTRY_CLOSE_CB/2 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ENTRY close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: ARCHIVE_CLOSE 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ARCHIVE close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: ARCHIVE_CLOSE_ 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ARCHIVE close_parent=1 symbol=814085 archive=0x61300002b8c0 entry=0x61a00000f680 agc=0
71: LIBARCHIVE_WRITE_CB 0x6060000129e0 0x61100000f540 (w) AR_OPENED_ARCHIVE close_parent=1 symbol=814085 archive=(nil) entry=0x61a00000f680 agc=0
71:
71: ***ARCHIVE_OPEN '/tmp/swipl_714659_5' read <stream>(0x611000050040)
71:
71: AR_W_ACQUIRE_CB 0x606000012a40 0x611000050040 (r) AR_VIRGIN close_parent=0 symbol=815237 archive=(nil) entry=(nil) agc=0
71: ARCHIVE_NEXT_HEADER 0x606000012a40 0x611000050040 (r) AR_OPENED_ARCHIVE close_parent=1 symbol=815237 archive=0x61d000041080 entry=(nil) agc=0
71: LIBARCHIVE_SKIP_CB 0x606000012a40 0x611000050040 (r) AR_OPENED_ARCHIVE close_parent=1 symbol=815237 archive=0x61d000041080 entry=(nil) agc=0
71: ARCHIVE_OPEN_ENTRY 0x606000012a40 0x611000050040 (r) AR_NEW_ENTRY close_parent=1 symbol=815237 archive=0x61d000041080 entry=0x61a000010e80 agc=0
71: ARCHIVE_CLOSE 0x606000012a40 0x611000050040 (r) AR_OPENED_ENTRY close_parent=1 symbol=815237 archive=0x61d000041080 entry=0x61a000010e80 agc=0
71: ARCHIVE_CLOSE_ 0x606000012a40 0x611000050040 (r) AR_OPENED_ENTRY close_parent=1 symbol=815237 archive=0x61d000041080 entry=0x61a000010e80 agc=0
71: AR_ENTRY_READ_CB 0x606000012a40 0x611000050040 (r) AR_OPENED_ENTRY_PENDING_CLOSE close_parent=1 symbol=815237 archive=0x61d000041080 entry=0x61a000010e80 agc=0
71: AR_ENTRY_READ_CB 0x606000012a40 0x611000050040 (r) AR_OPENED_ENTRY_PENDING_CLOSE close_parent=1 symbol=815237 archive=0x61d000041080 entry=0x61a000010e80 agc=0
71: AR_ENTRY_READ_CB 0x606000012a40 0x611000050040 (r) AR_OPENED_ENTRY_PENDING_CLOSE close_parent=1 symbol=815237 archive=0x61d000041080 entry=0x61a000010e80 agc=0
71: AR_ENTRY_READ_CB 0x606000012a40 0x611000050040 (r) AR_OPENED_ENTRY_PENDING_CLOSE close_parent=1 symbol=815237 archive=0x61d000041080 entry=0x61a000010e80 agc=0
71: AR_ENTRY_READ_CB 0x606000012a40 0x611000050040 (r) AR_OPENED_ENTRY_PENDING_CLOSE close_parent=1 symbol=815237 archive=0x61d000041080 entry=0x61a000010e80 agc=0
71: AR_ENTRY_READ_CB 0x606000012a40 0x611000050040 (r) AR_OPENED_ENTRY_PENDING_CLOSE close_parent=1 symbol=815237 archive=0x61d000041080 entry=0x61a000010e80 agc=0
71: AR_ENTRY_READ_CB 0x606000012a40 0x611000050040 (r) AR_OPENED_ENTRY_PENDING_CLOSE close_parent=1 symbol=815237 archive=0x61d000041080 entry=0x61a000010e80 agc=0
71: AR_ENTRY_READ_CB 0x606000012a40 0x611000050040 (r) AR_OPENED_ENTRY_PENDING_CLOSE close_parent=1 symbol=815237 archive=0x61d000041080 entry=0x61a000010e80 agc=0
71: .
71: ***GC TEST ***
71:
71: AR_W_RELEASE_CB 0x606000011840 0x61100002f200 (r) AR_ERROR close_parent=1 symbol=802949 archive=0x61d00003b680 entry=(nil) agc=1
71: AR_W_RELEASE_CB-done 0x606000011840 (nil) ( ) AR_RELEASED close_parent=0 symbol=0 archive=(nil) entry=(nil) agc=1
71: AR_W_RELEASE_CB 0x606000012080 (nil) (r) AR_VIRGIN close_parent=1 symbol=804229 archive=(nil) entry=(nil) agc=1
71: AR_W_RELEASE_CB-done 0x606000012080 (nil) ( ) AR_RELEASED close_parent=0 symbol=0 archive=(nil) entry=(nil) agc=1
71: AR_W_RELEASE_CB 0x6060000121a0 (nil) (r) AR_VIRGIN close_parent=1 symbol=804485 archive=(nil) entry=(nil) agc=1
71: AR_W_RELEASE_CB-done 0x6060000121a0 (nil) ( ) AR_RELEASED close_parent=0 symbol=0 archive=(nil) entry=(nil) agc=1
71: AR_W_RELEASE_CB 0x606000012560 (nil) (w) AR_VIRGIN close_parent=1 symbol=809477 archive=(nil) entry=(nil) agc=1
71: AR_W_RELEASE_CB-done 0x606000012560 (nil) ( ) AR_RELEASED close_parent=0 symbol=0 archive=(nil) entry=(nil) agc=1
71: AR_W_RELEASE_CB 0x606000012680 (nil) (r) AR_VIRGIN close_parent=1 symbol=811781 archive=(nil) entry=(nil) agc=1
71: AR_W_RELEASE_CB-done 0x606000012680 (nil) ( ) AR_RELEASED close_parent=0 symbol=0 archive=(nil) entry=(nil) agc=1
71: AR_W_RELEASE_CB 0x606000012800 (nil) (w) AR_VIRGIN close_parent=1 symbol=812293 archive=(nil) entry=(nil) agc=1
71: AR_W_RELEASE_CB-done 0x606000012800 (nil) ( ) AR_RELEASED close_parent=0 symbol=0 archive=(nil) entry=(nil) agc=1
71: AR_W_RELEASE_CB 0x606000012860 (nil) (r) AR_OPENED_ARCHIVE close_parent=1 symbol=813445 archive=(nil) entry=(nil) agc=1
71: AR_W_RELEASE_CB-done 0x606000012860 (nil) ( ) AR_RELEASED close_parent=0 symbol=0 archive=(nil) entry=(nil) agc=1
71: AR_W_RELEASE_CB 0x6060000129e0 (nil) (w) AR_VIRGIN close_parent=1 symbol=814085 archive=(nil) entry=(nil) agc=1
71: AR_W_RELEASE_CB-done 0x6060000129e0 (nil) ( ) AR_RELEASED close_parent=0 symbol=0 archive=(nil) entry=(nil) agc=1
71: . done
71: ***disable_gc
71: % All 6 tests passed
71: AR_ENTRY_CLOSE_CB 0x606000012a40 0x611000050040 (r) AR_OPENED_ENTRY_PENDING_CLOSE close_parent=1 symbol=815237 archive=0x61d000041080 entry=0x61a000010e80 agc=0
71: ARCHIVE_CLOSE_ 0x606000012a40 0x611000050040 (r) AR_OPENED_ARCHIVE close_parent=1 symbol=815237 archive=0x61d000041080 entry=0x61a000010e80 agc=0
71: =================================================================
71: ==714659==ERROR: AddressSanitizer: heap-use-after-free on address 0x611000050064 at pc 0x7f0ab9f6c852 bp 0x7ffe82e18820 sp 0x7ffe82e18810
71: READ of size 4 at 0x611000050064 thread T0
71: #0 0x7f0ab9f6c851 in S__close ../src/os/pl-stream.c:1933
71: #1 0x7f0ab9f6ced3 in Sclose ../src/os/pl-stream.c:2007
71: #2 0x7f0ab62cb361 in close_stream ../packages/archive/archive4pl.c:208
71: #3 0x7f0ab62d0c0e in ffi_archive_close_ ../packages/archive/archive4pl.c:1326
71: #4 0x7f0ab62d2ba0 in ar_entry_close_cb ../packages/archive/archive4pl.c:1628
71: #5 0x7f0ab9f6cc54 in S__close ../src/os/pl-stream.c:1976
71: #6 0x7f0ab9f6ced3 in Sclose ../src/os/pl-stream.c:2007
71: #7 0x7f0ab9f2ff19 in closeStream ../src/os/pl-file.c:1354
71: #8 0x7f0ab9f30136 in closeFiles ../src/os/pl-file.c:1386
71: #9 0x7f0ab9f2fcbb in dieIO ../src/os/pl-file.c:1301
71: #10 0x7f0ab9e53e7a in PL_cleanup ../src/pl-init.c:1541
71: #11 0x7f0ab9f1faf4 in haltProlog ../src/pl-fli.c:4603
71: #12 0x7f0ab9f1fb3c in PL_halt ../src/pl-fli.c:4615
71: #13 0x7f0ab9d697a6 in pl_halt ../src/pl-prims.c:5090
71: #14 0x7f0ab9c756e7 in PL_next_solution___LD ../src/pl-vmi.c:4626
71: #15 0x7f0ab9d710cb in query_loop ../src/pl-pro.c:146
71: #16 0x7f0ab9d72a01 in prologToplevel ../src/pl-pro.c:495
71: #17 0x7f0ab9f1fab9 in PL_toplevel ../src/pl-fli.c:4570
71: #18 0x5619ab05c280 in main ../src/pl-main.c:143
71: #19 0x7f0ab99c0082 in __libc_start_main ../csu/libc-start.c:308
71: #20 0x5619ab05c16d in _start (/home/peter/src/swipl-devel/build.sanitize/src/swipl+0x116d)
71:
71: 0x611000050064 is located 36 bytes inside of 256-byte region [0x611000050040,0x611000050140)
71: freed by thread T0 here:
71: #0 0x7f0aba3cc40f in __interceptor_free ../../../../src/libsanitizer/asan/asan_malloc_linux.cc:122
71: #1 0x7f0ab9ef357c in PL_free ../src/pl-alloc.c:1266
71: #2 0x7f0ab9f6c7f9 in unallocStream ../src/os/pl-stream.c:1916
71: #3 0x7f0ab9f6ce62 in S__close ../src/os/pl-stream.c:1998
71: #4 0x7f0ab9f6ced3 in Sclose ../src/os/pl-stream.c:2007
71: #5 0x7f0ab9f2ff19 in closeStream ../src/os/pl-file.c:1354
71: #6 0x7f0ab9f30136 in closeFiles ../src/os/pl-file.c:1386
71: #7 0x7f0ab9f2fcbb in dieIO ../src/os/pl-file.c:1301
71: #8 0x7f0ab9e53e7a in PL_cleanup ../src/pl-init.c:1541
71: #9 0x7f0ab9f1faf4 in haltProlog ../src/pl-fli.c:4603
71: #10 0x7f0ab9f1fb3c in PL_halt ../src/pl-fli.c:4615
71: #11 0x7f0ab9d697a6 in pl_halt ../src/pl-prims.c:5090
71: #12 0x7f0ab9c756e7 in PL_next_solution___LD ../src/pl-vmi.c:4626
71: #13 0x7f0ab9d710cb in query_loop ../src/pl-pro.c:146
71: #14 0x7f0ab9d72a01 in prologToplevel ../src/pl-pro.c:495
71: #15 0x7f0ab9f1fab9 in PL_toplevel ../src/pl-fli.c:4570
71: #16 0x5619ab05c280 in main ../src/pl-main.c:143
71: #17 0x7f0ab99c0082 in __libc_start_main ../csu/libc-start.c:308
71:
71: previously allocated by thread T0 here:
71: #0 0x7f0aba3cc808 in __interceptor_malloc ../../../../src/libsanitizer/asan/asan_malloc_linux.cc:144
71: #1 0x7f0ab9ef3456 in PL_malloc_uncollectable ../src/pl-alloc.c:1195
71: #2 0x7f0ab9f72687 in Snew ../src/os/pl-stream.c:3139
71: #3 0x7f0ab9f73432 in Sopen_file ../src/os/pl-stream.c:3364
71: #4 0x7f0ab9f3f5af in openStream ../src/os/pl-file.c:4029
71: #5 0x7f0ab9f40361 in pl_open44_va ../src/os/pl-file.c:4102
71: #6 0x7f0ab9c75435 in PL_next_solution___LD ../src/pl-vmi.c:4601
71: #7 0x7f0ab9d710cb in query_loop ../src/pl-pro.c:146
71: #8 0x7f0ab9d72a01 in prologToplevel ../src/pl-pro.c:495
71: #9 0x7f0ab9e52dde in PL_initialise ../src/pl-init.c:1233
71: #10 0x5619ab05c26d in main ../src/pl-main.c:139
71: #11 0x7f0ab99c0082 in __libc_start_main ../csu/libc-start.c:308
71:
71: SUMMARY: AddressSanitizer: heap-use-after-free ../src/os/pl-stream.c:1933 in S__close
71: Shadow bytes around the buggy address:
71: 0x0c2280001fb0: fa fa fa fa fa fa fa fa 00 00 00 00 00 00 00 00
71: 0x0c2280001fc0: 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00
71: 0x0c2280001fd0: 00 00 00 00 00 00 00 00 fa fa fa fa fa fa fa fa
71: 0x0c2280001fe0: 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00
71: 0x0c2280001ff0: 00 00 00 00 00 00 00 00 00 00 00 00 00 00 fa fa
71: =>0x0c2280002000: fa fa fa fa fa fa fa fa fd fd fd fd[fd]fd fd fd
71: 0x0c2280002010: fd fd fd fd fd fd fd fd fd fd fd fd fd fd fd fd
71: 0x0c2280002020: fd fd fd fd fd fd fd fd fa fa fa fa fa fa fa fa
71: 0x0c2280002030: 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00
71: 0x0c2280002040: 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00
71: 0x0c2280002050: fa fa fa fa fa fa fa fa fd fd fd fd fd fd fd fd
71: Shadow byte legend (one shadow byte represents 8 application bytes):
71: Addressable: 00
71: Partially addressable: 01 02 03 04 05 06 07
71: Heap left redzone: fa
71: Freed heap region: fd
71: Stack left redzone: f1
71: Stack mid redzone: f2
71: Stack right redzone: f3
71: Stack after return: f5
71: Stack use after scope: f8
71: Global redzone: f9
71: Global init order: f6
71: Poisoned by user: f7
71: Container overflow: fc
71: Array cookie: ac
71: Intra object redzone: bb
71: ASan internal: fe
71: Left alloca redzone: ca
71: Right alloca redzone: cb
71: Shadow gap: cc
71: ==714659==ABORTING
1/1 Test #71: archive:archive ..................***Failed 0.68 sec
0% tests passed, 1 tests failed out of 1
Total Test time (real) = 0.68 sec
The following tests FAILED:
71 - archive:archive (Failed)
Errors while running CTest
Compilation exited abnormally with code 8 at Thu Jun 2 16:34:09
Rationale for adding "release" field to IOFUNCTIONS
I propose adding a "release" field to IOFUNCTIONS, with a default
value of NULL. No code needs to be changed, although recompilation
of anything that uses IOFUNCTIONS will be necessary.
Usage: during garbage collection, if the stream has a "release"
function, "release" is called; otherwise "close" is called (as is
currently the situation). This is similar to how a blob is handled
(and a stream is a kind of blob) - a blob has a "release" that is
called during garbage collection; it can also have its own "close"
function (e.g., archive_close/1 for archives or close/1 for
streams). Many blobs don't need to distinguish between being released
due to garbage collection versus closed explicitly; but there are
situations where this information is needed.
IOFUNCTIONS.close is called in the following places:
S__close os/pl-stream.c:1976 (call)
closeWrappedIO os/pl-file.c:5663,5664 (called)
wrapIO os/pl-file.c:5709 (assigned)
It appears that only the usage in S__close() needs to be changed; and
that can be accomplished by adding an SIO_RELEASE flag (the
SIO_CLOSE_GC flag probably can't be used to mark this), and changing
the call to closeStream() in closeFiles(). [closeStream() is used only
within pl-file.c, so adding a flag to it is easy]
The following is an edited debug output and traceback. The debug
output shows that EntryStream's IOFUNCTIONS.close was called
(dieIO->...->S_close) with the blob's "close_parent" flag set, so an
attempt is made to close the "parent" stream. At this point, if the
close is because of a call to Prolog's close/1, the "parent" stream
should be closed; but if we're in garbage collection, the "parent"
stream should not be closed because regular garbage collection will
take care of it -- and, if we're in cleanup, the "parent" might have
already been closed because cleanup doesn't guarantee the order of
releasing atoms, which is why the use-after-free error occurs.
Snapshot of the files used, including the compilation and test:
https://gist.github.com/kamahen/75730c90611455921d307802ec57c19e
AR_ENTRY_CLOSE_CB (r) AR_OPENED_ENTRY_PENDING_CLOSE close_parent=1 agc=0
ARCHIVE_CLOSE_ (r) AR_OPENED_ARCHIVE close_parent=1 agc=0
=================================================================
==ERROR: AddressSanitizer: heap-use-after-free on address
#0 in S__close ../src/os/pl-stream.c:1933
#1 in Sclose ../src/os/pl-stream.c:2007
#2 in close_stream ../packages/archive/archive4pl.c:208
#3 in ffi_archive_close_ ../packages/archive/archive4pl.c:1326
#4 in ar_entry_close_cb ../packages/archive/archive4pl.c:1628
#5 in S__close ../src/os/pl-stream.c:1976
#6 in Sclose ../src/os/pl-stream.c:2007
#7 in closeStream ../src/os/pl-file.c:1354
#8 in closeFiles ../src/os/pl-file.c:1386
#9 in dieIO ../src/os/pl-file.c:1301
#10 in PL_cleanup ../src/pl-init.c:1541
#11 in haltProlog ../src/pl-fli.c:4603
...
/* Part of SWI-Prolog
Author: Jan Wielemaker and Peter Ludemann
E-mail: jan@swi-prolog.org
WWW: http://www.swi-prolog.org
Copyright (c) 2017-2022, VU University Amsterdam
SWI-Prolog Solutions b.v.
All rights reserved.
Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions
are met:
1. Redistributions of source code must retain the above copyright
notice, this list of conditions and the following disclaimer.
2. Redistributions in binary form must reproduce the above copyright
notice, this list of conditions and the following disclaimer in
the documentation and/or other materials provided with the
distribution.
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
POSSIBILITY OF SUCH DAMAGE.
*/
:- module(test_archive,
[ test_archive/0
]).
:- use_module(library(plunit)).
:- use_module(library(archive)).
:- use_module(library(apply), [maplist/3, maplist/2]).
:- use_module(library(filesex), [directory_file_path/3, relative_file_name/3]).
:- use_module(library(lists), [nth1/3]).
/* This is a very minimal test suite, which was written when fixing
some memory leak issues. */
test_archive :-
run_tests([ archive
]).
:- begin_tests(archive,
[ condition(archive_has_format(zip)),
% silent(false), % DO NOT SUBMIT
% concurrent(true), % DO NOT SUBMIT
% setup(disable_gc), % DO NOT SUBMIT
cleanup(( format(user_error, '***disable_gc~n', []), disable_gc ))
]).
% The following is derived from check_installation/0 for archive:
test(smoke_test_open1) :-
create_tmp_file(ArchivePath),
catch(archive_open(ArchivePath, A, []), E, true),
( var(E)
-> archive_close(A)
; true
),
delete_file(ArchivePath).
test(smoke_test_open2, [condition(current_prolog_flag(unix,true))]) :-
archive_open('/dev/null', A, []),
archive_close(A).
test(create_and_get_entries,
[FilesOut == Entries,
setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, _, FilesOut, _),
archive_entries(ArchivePath, Entries).
test(create_and_open_named_read,
[ContentsRead1 == Contents1,
setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, SrcDir, _, ExampleSourceFile),
file_contents(SrcDir, ExampleSourceFile, Contents1),
archive_open_named(ArchivePath, ExampleSourceFile, TestArchiveStream),
read_string(TestArchiveStream, _Len, ContentsRead1),
close(TestArchiveStream).
zztest(create_smoke_test,
[setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
archive_open(ArchivePath, write, ArchiveWrite, [format(zip)]),
archive_next_header(ArchiveWrite, 'not-foo'),
archive_open_entry(ArchiveWrite, EntryStreamWrite0),
close(EntryStreamWrite0),
archive_next_header(ArchiveWrite, ' foo '),
archive_open_entry(ArchiveWrite, EntryStreamWrite),
archive_close(ArchiveWrite),
format(string(Contents), 'Testing ~q', [ArchivePath]),
write(EntryStreamWrite, Contents),
close(EntryStreamWrite),
archive_close(ArchiveWrite).
zztest(create_and_open_named_write,
[ContentsRead == Contents,
setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
delete_file(ArchivePath),
archive_open(ArchivePath, write, ArchiveWrite, [format(zip)]),
archive_next_header(ArchiveWrite, 'not-foo'),
archive_open_entry(ArchiveWrite, EntryStreamWrite0),
write(EntryStreamWrite0, '***'),
close(EntryStreamWrite0),
archive_next_header(ArchiveWrite, ' foo '),
archive_open_entry(ArchiveWrite, EntryStreamWrite),
archive_close(ArchiveWrite),
format(string(Contents), 'Testing ~q', [ArchivePath]),
write(EntryStreamWrite, Contents),
close(EntryStreamWrite),
archive_close(ArchiveWrite),
archive_entries(ArchivePath, Entries),
% Note that this is not sort order - assume that zip doesn't sort
% the directory items:
assertion(Entries == ['not-foo', ' foo ']),
archive_open_named(ArchivePath, ' foo ', EntryStreamRead),
read_string(EntryStreamRead, _Len, ContentsRead),
close(EntryStreamRead).
% DO NOT SUBMIT - this test can cause use-after-free
test(create_and_open_named_no_close, % same as above but without close/1
[ContentsRead1 == Contents1,
setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, SrcDir, _, ExampleSourceFile),
file_contents(SrcDir, ExampleSourceFile, Contents1),
archive_open_named(ArchivePath, ExampleSourceFile, TestArchiveStream),
read_string(TestArchiveStream, _Len, ContentsRead1).
zztest(create_and_open_named_twice_no_close,
[ContentsRead1 == Contents1,
setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, SrcDir, _, ExampleSourceFile),
file_contents(SrcDir, ExampleSourceFile, Contents1),
archive_open_named(ArchivePath, 'swipl.rc', _Stream0),
archive_open_named(ArchivePath, ExampleSourceFile, TestArchiveStream),
read_string(TestArchiveStream, _Len, ContentsRead1).
zztest(create_and_open_named_fail, % Same as above but with bad EntryName
[fail,
setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, _, _, _),
archive_open_named(ArchivePath, 'XXX', _TestArchiveStream).
zztest(create_and_open_archive_entry,
[ContentsRead1 == Contents1,
setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, SrcDir, _, ExampleSourceFile),
file_contents(SrcDir, ExampleSourceFile, Contents1),
open_archive_entry(ArchivePath, ExampleSourceFile, TestArchiveStream),
read_string(TestArchiveStream, _Len, ContentsRead1),
close(TestArchiveStream).
zztest(create_and_open_archive_entry_no_close_1, % same as above but without close/1
[ContentsRead1 == Contents1,
setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, SrcDir, _, ExampleSourceFile),
file_contents(SrcDir, ExampleSourceFile, Contents1),
open_archive_entry(ArchivePath, ExampleSourceFile, TestArchiveStream),
read_string(TestArchiveStream, _Len, ContentsRead1).
zztest(create_and_open_archive_entry_no_close_2, % same as above but bad EntryName
[fail,
setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, _, _, _),
open_archive_entry(ArchivePath, 'XXXl', _TestArchiveStream).
zztest(create_and_entries_error,
[error(existence_error(file, 'foobar-qqsv'), _),
setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
FilesOut = ['foobar-qqsv'], % doesn't exist
archive_create(ArchivePath, FilesOut, [format(zip)]).
zztest(bad_unify_blob,
[fail,
setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
archive_open(ArchivePath, read, not_an_archive_blob, []).
zztest(bad_mode,
[error(domain_error(io_mode, neither_read_nor_write), _),
setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
archive_open(ArchivePath, neither_read_nor_write, _Archive, []).
zztest(double_open_write,
[fail,
setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
% This should fail because blob doesn't have PL_BLOB_UNIQUE
archive_open(ArchivePath, write, Archive, [format(zip)]),
archive_open(ArchivePath, write, Archive, [format(zip)]).
zztest(double_open_entry_write,
[error(permission_error('access-AR_OPENED_ENTRY(w)',archive_entry,Archive)),
setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
archive_open(ArchivePath, write, Archive, [format(zip)]),
archive_next_header(Archive, item1),
archive_open_entry(Archive, Stream1),
assertion(stream_property(Stream1, output)),
assertion(\+ stream_property(Stream1, input)),
archive_open_entry(Archive, _Stream2).
zztest(double_next_header_write,
[error(permission_error('next_header-AR_OPENED_ENTRY(w)',archive,Archive)),
setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
archive_open(ArchivePath, write, Archive, [format(zip)]),
archive_next_header(Archive, item1),
archive_open_entry(Archive, _Stream1),
archive_next_header(Archive, item2).
zztest(double_open_read,
[fail,
setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
% This should fail because blob doesn't have PL_BLOB_UNIQUE
create_archive_file(ArchivePath, _, _, _),
archive_open(ArchivePath, read, Archive, []),
archive_open(ArchivePath, read, Archive, []).
zztest(double_open_read2,
[setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, _, _, _),
% It's OK to open an archive twice for input with 2 different streams
archive_open(ArchivePath, read, Archive1, []),
archive_open(ArchivePath, read, Archive2, []),
archive_close(Archive1),
archive_close(Archive2).
zztest(double_open_entry_read,
[error(permission_error('access-AR_OPENED_ENTRY(r)',archive_entry,Archive)),
setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, _, _, ExampleSourceFile),
archive_open(ArchivePath, read, Archive, []),
archive_next_header(Archive, ExampleSourceFile),
archive_open_entry(Archive, Stream1),
assertion(stream_property(Stream1, input)),
assertion(\+ stream_property(Stream1, output)),
archive_open_entry(Archive, _Stream2).
zztest(double_next_header_read,
[error(permission_error('next_header-AR_OPENED_ENTRY(r)',archive,Archive)),
setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, _, FilesOut, _),
archive_open(ArchivePath, read, Archive, []),
FilesOut = [Item1, Item2 | _],
archive_next_header(Archive, Item1),
archive_open_entry(Archive, _Stream1),
archive_next_header(Archive, Item2).
zztest(next_header_order1,
[setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, _, FilesOut, _),
archive_open(ArchivePath, read, Archive, []),
archive_next_header(Archive, Item1),
archive_next_header(Archive, Item2),
assertion(ground(FilesOut)), % Ensure it's safe to use =/2 for next assertion
assertion(FilesOut = [Item1, Item2|_]),
archive_close(Archive).
zztest(next_header_order2,
[fail,
setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, _, FilesOut, _),
FilesOut = [Item1, Item2|_],
archive_open(ArchivePath, read, Archive, []),
archive_next_header(Archive, Item2),
archive_next_header(Archive, Item1). % Can only go forward
zztest(next_header_order3,
[setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, _, FilesOut, _),
FilesOut = [Item1, _Item2, Item3|_],
archive_open(ArchivePath, read, Archive, []),
archive_next_header(Archive, Item1),
archive_next_header(Archive, Item3), % Can skip forward
archive_close(Archive).
zztest(next_header_order4,
[setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, _, FilesOut, _),
FilesOut = [_Item1, Item2, Item3|_],
archive_open(ArchivePath, read, Archive, []),
archive_next_header(Archive, Item2),
archive_next_header(Archive, NextItem3),
assertion(NextItem3 == Item3),
archive_close(Archive).
zztest(close_parent1,
[setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, _, _FilesOut, Example),
open(ArchivePath, read, Stream, [type(binary)]),
assertion(is_stream(Stream)),
archive_open(Stream, read, Archive, [close_parent(false)]),
archive_next_header(Archive, Example),
archive_close(Archive),
assertion(is_stream(Stream)),
close(Stream),
assertion(\+ is_stream(Stream)).
zztest(close_parent2,
[setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, _, _FilesOut, Example),
open(ArchivePath, read, Stream, [type(binary)]),
assertion(is_stream(Stream)),
archive_open(Stream, read, Archive, [close_parent(true)]),
archive_next_header(Archive, Example),
archive_close(Archive),
assertion(\+ is_stream(Stream)).
% DO NOT SUBMIT - no error??? - if two close's on a single stream that
% had been "dup"ed with Snew(), then only the 2nd one
% takes effect?
% This is the error I was expecting:
% error(archive_error(_,fatal,Archive,archive_free)),
zztest(close_parent3,
[setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, _, _FilesOut, Example),
% Same as close_parent3, but has close(Stream) before archive_close(Archive).
open(ArchivePath, read, Stream, [type(binary)]),
assertion(is_stream(Stream)),
archive_open(Stream, read, Archive, [close_parent(true)]),
archive_next_header(Archive, Example),
close(Stream),
assertion(\+ is_stream(Stream)),
archive_close(Archive).
zztest(close_entry1,
[setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, _, _FilesOut, Example),
open(ArchivePath, read, Stream, [type(binary)]),
archive_open(Stream, read, Archive, [close_parent(false)]),
archive_next_header(Archive, Example),
archive_open_entry(Archive, ExampleStream),
read_line_to_string(ExampleStream, _ContentsRead1),
close(ExampleStream),
archive_close(Archive),
close(Stream).
zztest(close_entry2,
[setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, _, _FilesOut, Example),
% Like close_entry1, but ExampleStream is closed after archive_close/2
open(ArchivePath, read, Stream, [type(binary)]),
archive_open(Stream, read, Archive, [close_parent(false)]),
archive_next_header(Archive, Example),
archive_open_entry(Archive, ExampleStream),
read_line_to_string(ExampleStream, _ContentsRead1),
archive_close(Archive),
close(ExampleStream),
close(Stream).
zztest(close_entry3,
[ContentsRead1 == Contents1,
setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, SrcDir, _FilesOut, ExampleSourceFile),
file_contents(SrcDir, ExampleSourceFile, Contents1),
% Like close_entry1, but archive_close/2 is called while entry stream still open
open(ArchivePath, read, Stream, [type(binary)]),
archive_open(Stream, read, Archive, [close_parent(false)]),
archive_next_header(Archive, ExampleSourceFile),
archive_open_entry(Archive, ExampleStream),
archive_close(Archive),
read_string(ExampleStream, _Len, ContentsRead1).
zztest(close_entry4,
[error(archive_error(_,fatal,Archive,archive_read_next_header)),
setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, _, _FilesOut, Example),
% Like close_entry1, but Stream is closed before any archive actions
open(ArchivePath, read, Stream, [type(binary)]),
archive_open(Stream, read, Archive, [close_parent(false)]),
close(Stream),
archive_next_header(Archive, Example),
archive_open_entry(Archive, ExampleStream),
read_line_to_string(ExampleStream, _ContentsRead1),
close(ExampleStream),
archive_close(Archive).
zztest(no_next_header,
[error(permission_error('access-AR_OPENED_ARCHIVE(r)',archive_entry,Archive)),
setup(create_tmp_file(ArchivePath)),
cleanup(delete_file(ArchivePath))]) :-
create_archive_file(ArchivePath, _, _FilesOut, Example),
open(ArchivePath, read, Stream, [type(binary)]),
archive_open(Stream, read, Archive, [close_parent(false)]),
archive_open_entry(Archive, Example).
% This test can obscure some error situations form PL_cleanup(), but
% it might help in other debug situations. So, don't run it by default.
test(gc) :- % , [condition(true)]) :- % DO NOT SUBMIT
format(user_error, '~n***GC TEST ***~n~n', []),
% Do not set the agc_close_streams flag; it masks a use-after-free bug
% set_prolog_flag(agc_close_streams, true),
garbage_collect,
garbage_collect,
garbage_collect_atoms,
garbage_collect_atoms,
garbage_collect.
:- end_tests(archive).
disable_gc :-
set_prolog_flag(agc_margin,0), % turn off gc
% set_prolog_flag(trace_gc, true),
set_prolog_flag(agc_close_streams, true),
% set_prolog_flag(gc_thread, false),
% set_prolog_gc_thread(false),
trim_stacks,
garbage_collect,
garbage_collect_atoms.
create_tmp_file(Path) :-
tmp_file_stream(utf8, Path, Out),
close(Out).
%! create_archive_file(+ArchiveFile, -RootDir, -Files, -Example) is det.
%
% Create a `zip` archive using three files from the installed
% SWI-Prolog tree.
create_archive_file(ArchivePath, ArchiveSourceDir, FilesOut, ExampleSourceFile) :-
Files = [swi('include/SWI-Prolog.h'), library('archive.pl'), swi('swipl.rc')],
absolute_file_name(swi(.), ArchiveSourceDir, [file_type(directory), access(read)]),
maplist(ar_input(ArchiveSourceDir), Files, FilesOut),
nth1(2, FilesOut, ExampleSourceFile),
archive_create(ArchivePath, FilesOut,
[ format(zip),
directory(ArchiveSourceDir)
]).
ar_input(Dir, Spec, File) :-
directory_file_path(Dir, dummy, RelTo),
absolute_file_name(Spec, AbsFile, [access(read)]),
relative_file_name(AbsFile, RelTo, File).
archive_has_format(Format) :-
create_tmp_file(Path),
catch(archive_open(Path, A, [format(Format)]), E, true),
( var(E)
-> archive_close(A),
delete_file(Path)
; true
),
\+ subsumes_term(error(domain_error(format, _),_), E).
file_contents(SrcDir, File, Contents) :-
directory_file_path(SrcDir, File, Path),
setup_call_cleanup(
open(Path, read, In, [type(binary)]),
read_string(In, _Len, Contents),
close(In)).
% Code from documentation of archive_close/1.
archive_open_named(ArchiveFile, EntryName, EntryStream) :-
archive_open(ArchiveFile, Archive, []),
archive_next_header(Archive, EntryName),
archive_open_entry(Archive, EntryStream),
archive_close(Archive).
% DO NOT SUBMIT - test:
% open(File, Stream),
% archive_open(Stream, Archive)
% archive_next_header(...)
% archive_open_entry()
% close(Stream), % <=== also move this to other positions
% archive_close(Archive).
% Code from documentation of archive_close/1.
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).
% Code from documentation of module (1)
% TODO: make a test for this; for now,it's just done by hand.
list_archive(File) :-
setup_call_cleanup(
archive_open(File, Archive, []),
( repeat,
( archive_next_header(Archive, Path)
-> format('~w~n', [Path]),
fail
; !
)
),
archive_close(Archive)).
% Code from documentation of module (2)
% TODO: make a test for this; for now,it's just done by hand.
list_archive2(File) :-
list_archive2(File, Headers),
maplist(writeln, Headers).
list_archive2(File, Headers) :-
archive_foldl(add_header, File, Headers, []).
add_header(Path, _, [Path|Paths], Paths).
% Code from documentation of module (3)
% TODO: make a test for this; for now,it's just done by hand.
list_archive_headers(File) :-
archive_foldl(print_entry, File, 0, FileCount),
format('There are ~w files', [FileCount]).
print_entry(Path, Handle, Cnt0, Cnt1) :-
maplist(archive_header_property(Handle),
[filetype(Type), size(Size), permissions(Permissions), mtime(Mtime)]),
format_time(string(MtimeStr), '%d %b %Y %T %z', Mtime),
format('~|File ~w~t~30| type(~w) permissions(~|~`0t~8r~4+)~|~t~d~6+ bytes ~w~n',
[Path, Type, Permissions, Size, MtimeStr]),
Cnt1 is Cnt0 + 1.
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment