1/* Part of SWI-Prolog 2 3 Author: Jan Wielemaker 4 E-mail: jan@swi-prolog.org 5 WWW: https://www.swi-prolog.org 6 Copyright (c) 2012-2024, VU University Amsterdam 7 CWI, Amsterdam 8 SWI-Prolog Solutions b.v. 9 All rights reserved. 10 11 Redistribution and use in source and binary forms, with or without 12 modification, are permitted provided that the following conditions 13 are met: 14 15 1. Redistributions of source code must retain the above copyright 16 notice, this list of conditions and the following disclaimer. 17 18 2. Redistributions in binary form must reproduce the above copyright 19 notice, this list of conditions and the following disclaimer in 20 the documentation and/or other materials provided with the 21 distribution. 22 23 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 24 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 25 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 26 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 27 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 28 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 29 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 30 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 31 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 32 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 33 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 34 POSSIBILITY OF SUCH DAMAGE. 35*/ 36 37:- module(prolog_pack, 38 [ pack_list_installed/0, 39 pack_info/1, % +Name 40 pack_list/1, % +Keyword 41 pack_list/2, % +Query, +Options 42 pack_search/1, % +Keyword 43 pack_install/1, % +Name 44 pack_install/2, % +Name, +Options 45 pack_install_local/3, % :Spec, +Dir, +Options 46 pack_upgrade/1, % +Name 47 pack_rebuild/1, % +Name 48 pack_rebuild/0, % All packages 49 pack_remove/1, % +Name 50 pack_remove/2, % +Name, +Options 51 pack_publish/2, % +URL, +Options 52 pack_property/2 % ?Name, ?Property 53 ]). 54:- use_module(library(apply)). 55:- use_module(library(error)). 56:- use_module(library(option)). 57:- use_module(library(readutil)). 58:- use_module(library(lists)). 59:- use_module(library(filesex)). 60:- use_module(library(xpath)). 61:- use_module(library(settings)). 62:- use_module(library(uri)). 63:- use_module(library(dcg/basics)). 64:- use_module(library(dcg/high_order)). 65:- use_module(library(http/http_open)). 66:- use_module(library(json)). 67:- use_module(library(http/http_client), []). 68:- use_module(library(debug), [assertion/1]). 69:- use_module(library(pairs), 70 [pairs_keys/2, map_list_to_pairs/3, pairs_values/2]). 71:- autoload(library(git)). 72:- autoload(library(sgml)). 73:- autoload(library(sha)). 74:- autoload(library(build/tools)). 75:- autoload(library(ansi_term), [ansi_format/3]). 76:- autoload(library(pprint), [print_term/2]). 77:- autoload(library(prolog_versions), [require_version/3, cmp_versions/3]). 78:- autoload(library(ugraphs), [vertices_edges_to_ugraph/3, ugraph_layers/2]). 79:- autoload(library(process), [process_which/2]). 80:- autoload(library(aggregate), [aggregate_all/3]). 81 82:- meta_predicate 83 pack_install_local(, , ).
98 /******************************* 99 * CONSTANTS * 100 *******************************/ 101 102:- setting(server, atom, 'https://www.swi-prolog.org/pack/', 103 'Server to exchange pack information'). 104 105 106 /******************************* 107 * LOCAL DECLARATIONS * 108 *******************************/ 109 110:- op(900, xfx, @). % Token@Version 111 112:- meta_predicate det_if(,). 113 114 /******************************* 115 * PACKAGE INFO * 116 *******************************/
123current_pack(Pack) :- 124 current_pack(Pack, _). 125 126current_pack(Pack, Dir) :- 127 '$pack':pack(Pack, Dir).
134pack_list_installed :-
135 pack_list('', [installed(true)]),
136 validate_dependencies.142pack_info(Name) :- 143 pack_info(info, Name). 144 145pack_info(Level, Name) :- 146 must_be(atom, Name), 147 findall(Info, pack_info(Name, Level, Info), Infos0), 148 ( Infos0 == [] 149 -> print_message(warning, pack(no_pack_installed(Name))), 150 fail 151 ; true 152 ), 153 findall(Def, pack_default(Level, Infos, Def), Defs), 154 append(Infos0, Defs, Infos1), 155 sort(Infos1, Infos), 156 show_info(Name, Infos, [info(Level)]). 157 158 159show_info(_Name, _Properties, Options) :- 160 option(silent(true), Options), 161 !. 162show_info(_Name, _Properties, Options) :- 163 option(show_info(false), Options), 164 !. 165show_info(Name, Properties, Options) :- 166 option(info(list), Options), 167 !, 168 memberchk(title(Title), Properties), 169 memberchk(version(Version), Properties), 170 format('i ~w@~w ~28|- ~w~n', [Name, Version, Title]). 171show_info(Name, Properties, _) :- 172 !, 173 print_property_value('Package'-'~w', [Name]), 174 findall(Term, pack_level_info(info, Term, _, _), Terms), 175 maplist(print_property(Properties), Terms). 176 177print_property(_, nl) :- 178 !, 179 format('~n'). 180print_property(Properties, Term) :- 181 findall(Term, member(Term, Properties), Terms), 182 Terms \== [], 183 !, 184 pack_level_info(_, Term, LabelFmt, _Def), 185 ( LabelFmt = Label-FmtElem 186 -> true 187 ; Label = LabelFmt, 188 FmtElem = '~w' 189 ), 190 multi_valued(Terms, FmtElem, FmtList, Values), 191 atomic_list_concat(FmtList, ', ', Fmt), 192 print_property_value(Label-Fmt, Values). 193print_property(_, _). 194 195multi_valued([H], LabelFmt, [LabelFmt], Values) :- 196 !, 197 H =.. [_|Values]. 198multi_valued([H|T], LabelFmt, [LabelFmt|LT], Values) :- 199 H =.. [_|VH], 200 append(VH, MoreValues, Values), 201 multi_valued(T, LabelFmt, LT, MoreValues). 202 203 204pvalue_column(31). 205print_property_value(Prop-Fmt, Values) :- 206 !, 207 pvalue_column(C), 208 ansi_format(comment, '% ~w:~t~*|', [Prop, C]), 209 ansi_format(code, Fmt, Values), 210 ansi_format([], '~n', []). 211 212pack_info(Name, Level, Info) :- 213 '$pack':pack(Name, BaseDir), 214 pack_dir_info(BaseDir, Level, Info). 215 216pack_dir_info(BaseDir, Level, Info) :- 217 ( Info = directory(BaseDir) 218 ; pack_info_term(BaseDir, Info) 219 ), 220 pack_level_info(Level, Info, _Format, _Default). 221 222:- public pack_level_info/4. % used by web-server 223 224pack_level_info(_, title(_), 'Title', '<no title>'). 225pack_level_info(_, version(_), 'Installed version', '<unknown>'). 226pack_level_info(info, automatic(_), 'Automatic (dependency only)', -). 227pack_level_info(info, directory(_), 'Installed in directory', -). 228pack_level_info(info, link(_), 'Installed as link to'-'~w', -). 229pack_level_info(info, built(_,_), 'Built on'-'~w for SWI-Prolog ~w', -). 230pack_level_info(info, author(_, _), 'Author'-'~w <~w>', -). 231pack_level_info(info, maintainer(_, _), 'Maintainer'-'~w <~w>', -). 232pack_level_info(info, packager(_, _), 'Packager'-'~w <~w>', -). 233pack_level_info(info, home(_), 'Home page', -). 234pack_level_info(info, download(_), 'Download URL', -). 235pack_level_info(_, provides(_), 'Provides', -). 236pack_level_info(_, requires(_), 'Requires', -). 237pack_level_info(_, conflicts(_), 'Conflicts with', -). 238pack_level_info(_, replaces(_), 'Replaces packages', -). 239pack_level_info(info, library(_), 'Provided libraries', -). 240pack_level_info(info, autoload(_), 'Autoload', -). 241 242pack_default(Level, Infos, Def) :- 243 pack_level_info(Level, ITerm, _Format, Def), 244 Def \== (-), 245 \+ memberchk(ITerm, Infos).
251pack_info_term(BaseDir, Info) :- 252 directory_file_path(BaseDir, 'pack.pl', InfoFile), 253 catch( 254 term_in_file(valid_term(pack_info_term), InfoFile, Info), 255 error(existence_error(source_sink, InfoFile), _), 256 ( print_message(error, pack(no_meta_data(BaseDir))), 257 fail 258 )). 259pack_info_term(BaseDir, library(Lib)) :- 260 atom_concat(BaseDir, '/prolog/', LibDir), 261 atom_concat(LibDir, '*.pl', Pattern), 262 expand_file_name(Pattern, Files), 263 maplist(atom_concat(LibDir), Plain, Files), 264 convlist(base_name, Plain, Libs), 265 member(Lib, Libs), 266 Lib \== 'INDEX'. 267pack_info_term(BaseDir, autoload(true)) :- 268 atom_concat(BaseDir, '/prolog/INDEX.pl', IndexFile), 269 exists_file(IndexFile). 270pack_info_term(BaseDir, automatic(Boolean)) :- 271 once(pack_status_dir(BaseDir, automatic(Boolean))). 272pack_info_term(BaseDir, built(Arch, Prolog)) :- 273 pack_status_dir(BaseDir, built(Arch, Prolog, _How)). 274pack_info_term(BaseDir, link(Dest)) :- 275 read_link(BaseDir, _, Dest). 276 277base_name(File, Base) :- 278 file_name_extension(Base, pl, File).
call(Valid, Term) is true.284:- meta_predicate 285 term_in_file(, , ). 286 287term_in_file(Valid, File, Term) :- 288 exists_file(File), 289 setup_call_cleanup( 290 open(File, read, In, [encoding(utf8)]), 291 term_in_stream(Valid, In, Term), 292 close(In)). 293 294term_in_stream(Valid, In, Term) :- 295 repeat, 296 read_term(In, Term0, []), 297 ( Term0 == end_of_file 298 -> !, fail 299 ; Term = Term0, 300 call(Valid, Term0) 301 ). 302 303:- meta_predicate 304 valid_term(,). 305 306valid_term(Type, Term) :- 307 Term =.. [Name|Args], 308 same_length(Args, Types), 309 Decl =.. [Name|Types], 310 ( call(Type, Decl) 311 -> maplist(valid_info_arg, Types, Args) 312 ; print_message(warning, pack(invalid_term(Type, Term))), 313 fail 314 ). 315 316valid_info_arg(Type, Arg) :- 317 must_be(Type, Arg).
324pack_info_term(name(atom)). % Synopsis 325pack_info_term(title(atom)). 326pack_info_term(keywords(list(atom))). 327pack_info_term(description(list(atom))). 328pack_info_term(version(version)). 329pack_info_term(author(atom, email_or_url_or_empty)). % Persons 330pack_info_term(maintainer(atom, email_or_url)). 331pack_info_term(packager(atom, email_or_url)). 332pack_info_term(pack_version(nonneg)). % Package convention version 333pack_info_term(home(atom)). % Home page 334pack_info_term(download(atom)). % Source 335pack_info_term(provides(atom)). % Dependencies 336pack_info_term(requires(dependency)). 337pack_info_term(conflicts(dependency)). % Conflicts with package 338pack_info_term(replaces(atom)). % Replaces another package 339pack_info_term(autoload(boolean)). % Default installation options 340 341:- multifile 342 error:has_type/2. 343 344errorhas_type(version, Version) :- 345 atom(Version), 346 is_version(Version). 347errorhas_type(email_or_url, Address) :- 348 atom(Address), 349 ( sub_atom(Address, _, _, _, @) 350 -> true 351 ; uri_is_global(Address) 352 ). 353errorhas_type(email_or_url_or_empty, Address) :- 354 ( Address == '' 355 -> true 356 ; error:has_type(email_or_url, Address) 357 ). 358errorhas_type(dependency, Value) :- 359 is_dependency(Value). 360 361is_version(Version) :- 362 split_string(Version, ".", "", Parts), 363 maplist(number_string, _, Parts). 364 365is_dependency(Var) :- 366 var(Var), 367 !, 368 fail. 369is_dependency(Token) :- 370 atom(Token), 371 !. 372is_dependency(Term) :- 373 compound(Term), 374 compound_name_arguments(Term, Op, [Token,Version]), 375 atom(Token), 376 cmp(Op, _), 377 is_version(Version), 378 !. 379is_dependency(PrologToken) :- 380 is_prolog_token(PrologToken). 381 382cmp(<, @<). 383cmp(=<, @=<). 384cmp(==, ==). 385cmp(>=, @>=). 386cmp(>, @>). 387 388 389 /******************************* 390 * SEARCH * 391 *******************************/
Options processed:
installed(true).false, do not contact the server. This implies
installed(true). Otherwise, use the given pack server.
Hint: ?- pack_list(''). lists all known packages.
The predicates pack_list/1 and pack_search/1 are synonyms. Both
contact the package server at https://www.swi-prolog.org to find
available packages. Contacting the server can be avoided using the
server(false) option.
433pack_list(Query) :- 434 pack_list(Query, []). 435 436pack_search(Query) :- 437 pack_list(Query, []). 438 439pack_list(Query, Options) :- 440 ( option(installed(true), Options) 441 ; option(outdated(true), Options) 442 ; option(server(false), Options) 443 ), 444 !, 445 local_search(Query, Local), 446 maplist(arg(1), Local, Packs), 447 ( option(server(false), Options) 448 -> Hits = [] 449 ; query_pack_server(info(Packs), true(Hits), Options) 450 ), 451 list_hits(Hits, Local, Options). 452pack_list(Query, Options) :- 453 query_pack_server(search(Query), Result, Options), 454 ( Result == false 455 -> ( local_search(Query, Packs), 456 Packs \== [] 457 -> forall(member(pack(Pack, Stat, Title, Version, _), Packs), 458 format('~w ~w@~w ~28|- ~w~n', 459 [Stat, Pack, Version, Title])) 460 ; print_message(warning, pack(search_no_matches(Query))) 461 ) 462 ; Result = true(Hits), % Hits = list(pack(Name, p, Title, Version, URL)) 463 local_search(Query, Local), 464 list_hits(Hits, Local, []) 465 ). 466 467list_hits(Hits, Local, Options) :- 468 append(Hits, Local, All), 469 sort(All, Sorted), 470 join_status(Sorted, Packs0), 471 include(filtered(Options), Packs0, Packs), 472 maplist(list_hit(Options), Packs). 473 474filtered(Options, pack(_,Tag,_,_,_)) :- 475 option(outdated(true), Options), 476 !, 477 Tag == 'U'. 478filtered(_, _). 479 480list_hit(_Options, pack(Pack, Tag, Title, Version, _URL)) => 481 list_tag(Tag), 482 ansi_format(code, '~w', [Pack]), 483 format('@'), 484 list_version(Tag, Version), 485 format('~35|- ', []), 486 ansi_format(comment, '~w~n', [Title]). 487 488list_tag(Tag) :- 489 tag_color(Tag, Color), 490 ansi_format(Color, '~w ', [Tag]). 491 492list_version(Tag, VersionI-VersionS) => 493 tag_color(Tag, Color), 494 ansi_format(Color, '~w', [VersionI]), 495 ansi_format(bold, '(~w)', [VersionS]). 496list_version(_Tag, Version) => 497 ansi_format([], '~w', [Version]). 498 499tag_color('U', warning) :- !. 500tag_color('A', comment) :- !. 501tag_color(_, []).
pack(Name, Status, Version, URL). If
the versions do not match, Version is
VersionInstalled-VersionRemote and similar for thee URL.510join_status([], []). 511join_status([ pack(Pack, i, Title, Version, URL), 512 pack(Pack, p, Title, Version, _) 513 | T0 514 ], 515 [ pack(Pack, Tag, Title, Version, URL) 516 | T 517 ]) :- 518 !, 519 ( pack_status(Pack, automatic(true)) 520 -> Tag = a 521 ; Tag = i 522 ), 523 join_status(T0, T). 524join_status([ pack(Pack, i, Title, VersionI, URLI), 525 pack(Pack, p, _, VersionS, URLS) 526 | T0 527 ], 528 [ pack(Pack, Tag, Title, VersionI-VersionS, URLI-URLS) 529 | T 530 ]) :- 531 !, 532 version_sort_key(VersionI, VDI), 533 version_sort_key(VersionS, VDS), 534 ( VDI @< VDS 535 -> Tag = 'U' 536 ; Tag = 'A' 537 ), 538 join_status(T0, T). 539join_status([ pack(Pack, i, Title, VersionI, URL) 540 | T0 541 ], 542 [ pack(Pack, l, Title, VersionI, URL) 543 | T 544 ]) :- 545 !, 546 join_status(T0, T). 547join_status([H|T0], [H|T]) :- 548 join_status(T0, T).
554local_search(Query, Packs) :- 555 findall(Pack, matching_installed_pack(Query, Pack), Packs). 556 557matching_installed_pack(Query, pack(Pack, i, Title, Version, URL)) :- 558 current_pack(Pack), 559 findall(Term, 560 ( pack_info(Pack, _, Term), 561 search_info(Term) 562 ), Info), 563 ( sub_atom_icasechk(Pack, _, Query) 564 -> true 565 ; memberchk(title(Title), Info), 566 sub_atom_icasechk(Title, _, Query) 567 ), 568 option(title(Title), Info, '<no title>'), 569 option(version(Version), Info, '<no version>'), 570 option(download(URL), Info, '<no download url>'). 571 572search_info(title(_)). 573search_info(version(_)). 574search_info(download(_)). 575 576 577 /******************************* 578 * INSTALL * 579 *******************************/
http(s) URL of an archive file name. This URL may contain a
star (*) for the version. In this case pack_install/1 asks
for the directory content and selects the latest version.file:// URL'.', in which case a relative symlink is created to the
current directory (all other options for Spec make a copy
of the files). Installation using a symlink is normally
used during development of a pack.
Processes the options below. Default options as would be used by
pack_install/1 are used to complete the provided Options. Note that
pack_install/2 can be used through the SWI-Prolog command line app
pack as below. Most of the options of this predicate are available
as command line options.
swipl pack install <name>
Options:
true, install in the XDG common application data path,
making the pack accessible to everyone. If false, install in
the XDG user application data path, making the pack accessible
for the current user only. If the option is absent, use the
first existing and writable directory. If that doesn't exist
find locations where it can be created and prompt the user to do
so.true (default false), do not perform any checks on SSL
certificates when downloading using https.true (default false), suppress informational progress
messages.true (default false), upgrade package if it is already
installed.if_absent (default, do nothing if the directory with foreign
resources exists), make (run make) or true (run `make
distclean` followed by the default configure and build steps).true (default), run the pack tests.true (default false unless URL ends with .git),
assume the URL is a GIT repository.'1.5' is the
same as >=('1.5').'HEAD'.-DCMAKE_BUILD_TYPE=Type.
Default is the build type of Prolog or Release.true (default), register packages as downloaded after
performing the download. This contacts the server with the
meta-data of each pack that was downloaded. The server will
either register the location as a new version or increment
the download count. The server stores the IP address of the
client. Subsequent downloads of the same version from the
same IP address are ignored.prolog_pack:server, by default set to
https://www.swi-prolog.org/pack/
Non-interactive installation can be established using the option
interactive(false). It is adviced to install from a particular
trusted URL instead of the plain pack name for unattented
operation.
679pack_install(Spec) :- 680 pack_default_options(Spec, Pack, [], Options), 681 pack_install(Pack, [pack(Pack)|Options]). 682 683pack_install(Specs, Options) :- 684 is_list(Specs), 685 !, 686 maplist(pack_options(Options), Specs, Pairs), 687 pack_install_dir(PackTopDir, Options), 688 pack_install_set(Pairs, PackTopDir, Options). 689pack_install(Spec, Options) :- 690 pack_default_options(Spec, Pack, Options, DefOptions), 691 ( option(already_installed(Installed), DefOptions) 692 -> print_message(informational, pack(already_installed(Installed))) 693 ; merge_options(Options, DefOptions, PackOptions), 694 pack_install_dir(PackTopDir, PackOptions), 695 pack_install_set([Pack-PackOptions], PackTopDir, Options) 696 ). 697 698pack_options(Options, Spec, Pack-PackOptions) :- 699 pack_default_options(Spec, Pack, Options, DefOptions), 700 merge_options(Options, DefOptions, PackOptions).
url(URL) option. Determine whether
the URL is a GIT repository, get the version and pack from the
URL.git(true)
and adds the URL as option.packs.pl
file.'.'. Create a symlink to make the current dir
accessible as a pack.726pack_default_options(_Spec, Pack, OptsIn, Options) :- % (1) 727 option(already_installed(pack(Pack,_Version)), OptsIn), 728 !, 729 Options = OptsIn. 730pack_default_options(_Spec, Pack, OptsIn, Options) :- % (2) 731 option(url(URL), OptsIn), 732 !, 733 ( option(git(_), OptsIn) 734 -> Options = OptsIn 735 ; git_url(URL, Pack) 736 -> Options = [git(true)|OptsIn] 737 ; Options = OptsIn 738 ), 739 ( nonvar(Pack) 740 -> true 741 ; option(pack(Pack), Options) 742 -> true 743 ; pack_version_file(Pack, _Version, URL) 744 ). 745pack_default_options(Archive, Pack, OptsIn, Options) :- % (3) 746 must_be(atom, Archive), 747 \+ uri_is_global(Archive), 748 expand_file_name(Archive, [File]), 749 exists_file(File), 750 !, 751 ( pack_version_file(Pack, Version, File) 752 -> uri_file_name(FileURL, File), 753 merge_options([url(FileURL), version(Version)], OptsIn, Options) 754 ; domain_error(pack_file_name, Archive) 755 ). 756pack_default_options(URL, Pack, OptsIn, Options) :- % (4) 757 git_url(URL, Pack), 758 !, 759 merge_options([git(true), url(URL)], OptsIn, Options). 760pack_default_options(FileURL, Pack, _, Options) :- % (5) 761 uri_file_name(FileURL, Dir), 762 exists_directory(Dir), 763 pack_info_term(Dir, name(Pack)), 764 !, 765 ( pack_info_term(Dir, version(Version)) 766 -> uri_file_name(DirURL, Dir), 767 Options = [url(DirURL), version(Version)] 768 ; throw(error(existence_error(key, version, Dir),_)) 769 ). 770pack_default_options('.', Pack, OptsIn, Options) :- % (6) 771 pack_info_term('.', name(Pack)), 772 !, 773 working_directory(Dir, Dir), 774 ( pack_info_term(Dir, version(Version)) 775 -> uri_file_name(DirURL, Dir), 776 NewOptions = [url(DirURL), version(Version) | Options1], 777 ( current_prolog_flag(windows, true) 778 -> Options1 = [] 779 ; Options1 = [link(true), rebuild(make)] 780 ), 781 merge_options(NewOptions, OptsIn, Options) 782 ; throw(error(existence_error(key, version, Dir),_)) 783 ). 784pack_default_options(URL, Pack, OptsIn, Options) :- % (7) 785 pack_version_file(Pack, Version, URL), 786 download_url(URL), 787 !, 788 available_download_versions(URL, Available, Options), 789 Available = [URLVersion-LatestURL|_], 790 NewOptions = [url(LatestURL)|VersionOptions], 791 version_options(Version, URLVersion, Available, VersionOptions), 792 merge_options(NewOptions, OptsIn, Options). 793pack_default_options(Pack, Pack, Options, Options) :- % (8) 794 \+ uri_is_global(Pack). 795 796version_options(Version, Version, _, [version(Version)]) :- !. 797version_options(Version, _, Available, [versions(Available)]) :- 798 sub_atom(Version, _, _, _, *), 799 !. 800version_options(_, _, _, []).
pack_directory(+PackDir)
Use PackDir. PackDir is created if it does not exist.global(+Boolean)
If true, find a writeable global directory based on the
file search path common_app_data. If false, find a
user-specific writeable directory based on user_app_datapack.If no writeable directory is found, generate possible location where this directory can be created and ask the user to create one of them.
820pack_install_dir(PackDir, Options) :- 821 option(pack_directory(PackDir), Options), 822 ensure_directory(PackDir), 823 !. 824pack_install_dir(PackDir, Options) :- 825 base_alias(Alias, Options), 826 absolute_file_name(Alias, PackDir, 827 [ file_type(directory), 828 access(write), 829 file_errors(fail) 830 ]), 831 !. 832pack_install_dir(PackDir, Options) :- 833 pack_create_install_dir(PackDir, Options). 834 835base_alias(Alias, Options) :- 836 option(global(true), Options), 837 !, 838 Alias = common_app_data(pack). 839base_alias(Alias, Options) :- 840 option(global(false), Options), 841 !, 842 Alias = user_app_data(pack). 843base_alias(Alias, _Options) :- 844 Alias = pack('.'). 845 846pack_create_install_dir(PackDir, Options) :- 847 base_alias(Alias, Options), 848 findall(Candidate = create_dir(Candidate), 849 ( absolute_file_name(Alias, Candidate, [solutions(all)]), 850 \+ exists_file(Candidate), 851 \+ exists_directory(Candidate), 852 file_directory_name(Candidate, Super), 853 ( exists_directory(Super) 854 -> access_file(Super, write) 855 ; true 856 ) 857 ), 858 Candidates0), 859 list_to_set(Candidates0, Candidates), % keep order 860 pack_create_install_dir(Candidates, PackDir, Options). 861 862pack_create_install_dir(Candidates, PackDir, Options) :- 863 Candidates = [Default=_|_], 864 !, 865 append(Candidates, [cancel=cancel], Menu), 866 menu(pack(create_pack_dir), Menu, Default, Selected, Options), 867 Selected \== cancel, 868 ( catch(make_directory_path(Selected), E, 869 (print_message(warning, E), fail)) 870 -> PackDir = Selected 871 ; delete(Candidates, PackDir=create_dir(PackDir), Remaining), 872 pack_create_install_dir(Remaining, PackDir, Options) 873 ). 874pack_create_install_dir(_, _, _) :- 875 print_message(error, pack(cannot_create_dir(pack(.)))), 876 fail.
890pack_unpack_from_local(Source0, PackTopDir, Name, PackDir, Options) :- 891 exists_directory(Source0), 892 remove_slash(Source0, Source), 893 !, 894 directory_file_path(PackTopDir, Name, PackDir), 895 ( option(link(true), Options) 896 -> ( same_file(Source, PackDir) 897 -> true 898 ; remove_existing_pack(PackDir, Options), 899 atom_concat(PackTopDir, '/', PackTopDirS), 900 relative_file_name(Source, PackTopDirS, RelPath), 901 link_file(RelPath, PackDir, symbolic), 902 assertion(same_file(Source, PackDir)) 903 ) 904 ; \+ option(git(false), Options), 905 is_git_directory(Source) 906 -> remove_existing_pack(PackDir, Options), 907 run_process(path(git), [clone, Source, PackDir], []) 908 ; prepare_pack_dir(PackDir, Options), 909 copy_directory(Source, PackDir) 910 ). 911pack_unpack_from_local(Source, PackTopDir, Name, PackDir, Options) :- 912 exists_file(Source), 913 directory_file_path(PackTopDir, Name, PackDir), 914 prepare_pack_dir(PackDir, Options), 915 pack_unpack(Source, PackDir, Name, Options).
924:- if(exists_source(library(archive))). 925pack_unpack(Source, PackDir, Pack, Options) :- 926 ensure_loaded_archive, 927 pack_archive_info(Source, Pack, _Info, StripOptions), 928 prepare_pack_dir(PackDir, Options), 929 archive_extract(Source, PackDir, 930 [ exclude(['._*']) % MacOS resource forks 931 | StripOptions 932 ]). 933:- else. 934pack_unpack(_,_,_,_) :- 935 existence_error(library, archive). 936:- endif.
944pack_install_local(M:Gen, Dir, Options) :- 945 findall(Pack-PackOptions, call(M:Gen, Pack, PackOptions), Pairs), 946 pack_install_set(Pairs, Dir, Options). 947 948pack_install_set(Pairs, Dir, Options) :- 949 must_be(list(pair), Pairs), 950 ensure_directory(Dir), 951 partition(known_media, Pairs, Local, Remote), 952 maplist(pack_options_to_versions, Local, LocalVersions), 953 ( Remote == [] 954 -> AllVersions = LocalVersions 955 ; pairs_keys(Remote, Packs), 956 prolog_description(Properties), 957 query_pack_server(versions(Packs, Properties), Result, Options), 958 ( Result = true(RemoteVersions) 959 -> append(LocalVersions, RemoteVersions, AllVersions) 960 ; print_message(error, pack(query_failed(Result))), 961 fail 962 ) 963 ), 964 local_packs(Dir, Existing), 965 pack_resolve(Pairs, Existing, AllVersions, Plan0, Options), 966 !, % for now, only first plan 967 maplist(hsts_info(Options), Plan0, Plan), 968 Options1 = [pack_directory(Dir)|Options], 969 download_plan(Pairs, Plan, PlanB, Options1), 970 register_downloads(PlanB, Options), 971 maplist(update_automatic, PlanB), 972 build_plan(PlanB, Built, Options1), 973 publish_download(PlanB, Options), 974 work_done(Pairs, Plan, PlanB, Built, Options). 975 976hsts_info(Options, Info0, Info) :- 977 hsts(Info0.get(url), URL, Options), 978 !, 979 Info = Info0.put(url, URL). 980hsts_info(_Options, Info, Info).
989known_media(_-Options) :-
990 option(url(_), Options).pack(Pack, i, Title, Version, URL) terms that represents the already
installed packages. Versions is obtained from the server. See
pack.pl from the web server for details. On success, this results
in a Plan to satisfies the requirements. The plan is a list of
packages to install with their location. The steps satisfy the
partial ordering of dependencies, such that dependencies are
installed before the dependents. Options:
1008pack_resolve(Pairs, Existing, Versions, Plan, Options) :-
1009 insert_existing(Existing, Versions, AllVersions, Options),
1010 phrase(select_version(Pairs, AllVersions,
1011 [ plan(PlanA), % access to plan
1012 dependency_for([]) % dependencies
1013 | Options
1014 ]),
1015 PlanA),
1016 mark_installed(PlanA, Existing, Plan).upgrade(true) is specified, the existing is merged into the set of
Available versions. Otherwise Existing is prepended to Available, so
it is selected as first.1027:- det(insert_existing/4). 1028insert_existing(Existing, [], Versions, _Options) => 1029 maplist(existing_to_versions, Existing, Versions). 1030insert_existing(Existing, [Pack-Versions|T0], AllPackVersions, Options), 1031 select(Installed, Existing, Existing2), 1032 Installed.pack == Pack => 1033 can_upgrade(Installed, Versions, Installed2), 1034 insert_existing_(Installed2, Versions, AllVersions, Options), 1035 AllPackVersions = [Pack-AllVersions|T], 1036 insert_existing(Existing2, T0, T, Options). 1037insert_existing(Existing, [H|T0], AllVersions, Options) => 1038 AllVersions = [H|T], 1039 insert_existing(Existing, T0, T, Options). 1040 1041existing_to_versions(Installed, Pack-[Version-[Installed]]) :- 1042 Pack = Installed.pack, 1043 Version = Installed.version. 1044 1045insert_existing_(Installed, Versions, AllVersions, Options) :- 1046 option(upgrade(true), Options), 1047 !, 1048 insert_existing_(Installed, Versions, AllVersions). 1049insert_existing_(Installed, Versions, AllVersions, _) :- 1050 AllVersions = [Installed.version-[Installed]|Versions]. 1051 1052insert_existing_(Installed, [H|T0], [H|T]) :- 1053 H = V0-_Infos, 1054 cmp_versions(>, V0, Installed.version), 1055 !, 1056 insert_existing_(Installed, T0, T). 1057insert_existing_(Installed, [H0|T], [H|T]) :- 1058 H0 = V0-Infos, 1059 V0 == Installed.version, 1060 !, 1061 H = V0-[Installed|Infos]. 1062insert_existing_(Installed, Versions, All) :- 1063 All = [Installed.version-[Installed]|Versions].
latest_version key to Installed if its version is older than
the latest available version.1070can_upgrade(Info, [Version-_|_], Info2) :- 1071 cmp_versions(>, Version, Info.version), 1072 !, 1073 Info2 = Info.put(latest_version, Version). 1074can_upgrade(Info, _, Info).
upgrade:true to elements of PlanA in Existing that are not the
same.1082mark_installed([], _, []). 1083mark_installed([Info|T], Existing, Plan) :- 1084 ( member(Installed, Existing), 1085 Installed.pack == Info.pack 1086 -> ( ( Installed.git == true 1087 -> Info.git == true, 1088 Installed.hash == Info.hash 1089 ; Version = Info.get(version) 1090 -> Installed.version == Version 1091 ) 1092 -> Plan = [Info.put(keep, true)|PlanT] % up-to-date 1093 ; Plan = [Info.put(upgrade, Installed)|PlanT] % needs upgrade 1094 ) 1095 ; Plan = [Info|PlanT] % new install 1096 ), 1097 mark_installed(T, Existing, PlanT).
1105select_version([], _, _) --> 1106 []. 1107select_version([Pack-PackOptions|More], Versions, Options) --> 1108 { memberchk(Pack-PackVersions, Versions), 1109 member(Version-Infos, PackVersions), 1110 compatible_version(Pack, Version, PackOptions), 1111 member(Info, Infos), 1112 pack_options_compatible_with_info(Info, PackOptions), 1113 pack_satisfies(Pack, Version, Info, Info2, PackOptions), 1114 all_downloads(PackVersions, Downloads) 1115 }, 1116 add_to_plan(Info2.put(_{version: Version, all_downloads:Downloads}), 1117 Versions, Options), 1118 select_version(More, Versions, Options). 1119select_version([Pack-_PackOptions|_More], _Versions, _Options) --> 1120 { existence_error(pack, Pack) }. % or warn and continue? 1121 1122all_downloads(PackVersions, AllDownloads) :- 1123 aggregate_all(sum(Downloads), 1124 ( member(_Version-Infos, PackVersions), 1125 member(Info, Infos), 1126 get_dict(downloads, Info, Downloads) 1127 ), 1128 AllDownloads). 1129 1130add_requirements([], _, _) --> 1131 []. 1132add_requirements([H|T], Versions, Options) --> 1133 { is_prolog_token(H), 1134 !, 1135 prolog_satisfies(H) 1136 }, 1137 add_requirements(T, Versions, Options). 1138add_requirements([H|T], Versions, Options) --> 1139 { member(Pack-PackVersions, Versions), 1140 member(Version-Infos, PackVersions), 1141 member(Info, Infos), 1142 ( Provides = @(Pack,Version) 1143 ; member(Provides, Info.get(provides)) 1144 ), 1145 satisfies_req(Provides, H), 1146 all_downloads(PackVersions, Downloads) 1147 }, 1148 add_to_plan(Info.put(_{version: Version, all_downloads:Downloads}), 1149 Versions, Options), 1150 add_requirements(T, Versions, Options).
1158add_to_plan(Info, _Versions, Options) --> 1159 { option(plan(Plan), Options), 1160 member_nonvar(Planned, Plan), 1161 Planned.pack == Info.pack, 1162 !, 1163 same_version(Planned, Info) % same pack, different version 1164 }. 1165add_to_plan(Info, _Versions, _Options) --> 1166 { member(Conflict, Info.get(conflicts)), 1167 is_prolog_token(Conflict), 1168 prolog_satisfies(Conflict), 1169 !, 1170 fail % incompatible with this Prolog 1171 }. 1172add_to_plan(Info, _Versions, Options) --> 1173 { option(plan(Plan), Options), 1174 member_nonvar(Planned, Plan), 1175 info_conflicts(Info, Planned), % Conflicts with a planned pack 1176 !, 1177 fail 1178 }. 1179add_to_plan(Info, Versions, Options) --> 1180 { select_option(dependency_for(Dep0), Options, Options1), 1181 Options2 = [dependency_for([Info.pack|Dep0])|Options1], 1182 ( Dep0 = [DepFor|_] 1183 -> add_dependency_for(DepFor, Info, Info1) 1184 ; Info1 = Info 1185 ) 1186 }, 1187 [Info1], 1188 add_requirements(Info.get(requires,[]), Versions, Options2). 1189 1190add_dependency_for(Pack, Info, Info) :- 1191 Old = Info.get(dependency_for), 1192 !, 1193 b_set_dict(dependency_for, Info, [Pack|Old]). 1194add_dependency_for(Pack, Info0, Info) :- 1195 Info = Info0.put(dependency_for, [Pack]). 1196 1197same_version(Info, Info) :- 1198 !. 1199same_version(Planned, Info) :- 1200 Hash = Planned.get(hash), 1201 Hash \== (-), 1202 !, 1203 Hash == Info.get(hash). 1204same_version(Planned, Info) :- 1205 Planned.get(version) == Info.get(version).
1211info_conflicts(Info, Planned) :- 1212 info_conflicts_(Info, Planned), 1213 !. 1214info_conflicts(Info, Planned) :- 1215 info_conflicts_(Planned, Info), 1216 !. 1217 1218info_conflicts_(Info, Planned) :- 1219 member(Conflict, Info.get(conflicts)), 1220 \+ is_prolog_token(Conflict), 1221 info_provides(Planned, Provides), 1222 satisfies_req(Provides, Conflict), 1223 !. 1224 1225info_provides(Info, Provides) :- 1226 ( Provides = Info.pack@Info.version 1227 ; member(Provides, Info.get(provides)) 1228 ).
1235pack_satisfies(_Pack, _Version, Info0, Info, Options) :- 1236 option(commit('HEAD'), Options), 1237 !, 1238 Info0.get(git) == true, 1239 Info = Info0.put(commit, 'HEAD'). 1240pack_satisfies(_Pack, _Version, Info, Info, Options) :- 1241 option(commit(Commit), Options), 1242 !, 1243 Commit == Info.get(hash). 1244pack_satisfies(Pack, Version, Info, Info, Options) :- 1245 option(version(ReqVersion), Options), 1246 !, 1247 satisfies_version(Pack, Version, ReqVersion). 1248pack_satisfies(_Pack, _Version, Info, Info, _Options).
1252satisfies_version(Pack, Version, ReqVersion) :-
1253 catch(require_version(pack(Pack), Version, ReqVersion),
1254 error(version_error(pack(Pack), Version, ReqVersion),_),
1255 fail).1261satisfies_req(Token, Token) => true. 1262satisfies_req(@(Token,_), Token) => true. 1263satisfies_req(@(Token,PrvVersion), Req), cmp(Req, Token, Cmp, ReqVersion) => 1264 cmp_versions(Cmp, PrvVersion, ReqVersion). 1265satisfies_req(_,_) => fail. 1266 1267cmp(Token < Version, Token, <, Version). 1268cmp(Token =< Version, Token, =<, Version). 1269cmp(Token = Version, Token, =, Version). 1270cmp(Token == Version, Token, ==, Version). 1271cmp(Token >= Version, Token, >=, Version). 1272cmp(Token > Version, Token, >, Version).
url(URL) option. This allows installing packages that are
not known to the server. In most cases, the URL will be a git URL or
the URL to download an archive. It can also be a file:// url to
install from a local archive.
The first clause deals with a wildcard URL. See pack_default_options/4, case (7).
1285:- det(pack_options_to_versions/2). 1286pack_options_to_versions(Pack-PackOptions, Pack-Versions) :- 1287 option(versions(Available), PackOptions), !, 1288 maplist(version_url_info(Pack, PackOptions), Available, Versions). 1289pack_options_to_versions(Pack-PackOptions, Pack-[Version-[Info]]) :- 1290 option(url(URL), PackOptions), 1291 findall(Prop, option_info_prop(PackOptions, Prop), Pairs), 1292 dict_create(Info, #, 1293 [ pack-Pack, 1294 url-URL 1295 | Pairs 1296 ]), 1297 Version = Info.get(version, '0.0.0'). 1298 1299version_url_info(Pack, PackOptions, Version-URL, Version-[Info]) :- 1300 findall(Prop, 1301 ( option_info_prop(PackOptions, Prop), 1302 Prop \= version-_ 1303 ), 1304 Pairs), 1305 dict_create(Info, #, 1306 [ pack-Pack, 1307 url-URL, 1308 version-Version 1309 | Pairs 1310 ]). 1311 1312option_info_prop(PackOptions, Prop-Value) :- 1313 option_info(Prop), 1314 Opt =.. [Prop,Value], 1315 option(Opt, PackOptions). 1316 1317option_info(git). 1318option_info(hash). 1319option_info(version). 1320option_info(branch). 1321option_info(link).
1328compatible_version(Pack, Version, PackOptions) :- 1329 option(version(ReqVersion), PackOptions), 1330 !, 1331 satisfies_version(Pack, Version, ReqVersion). 1332compatible_version(_, _, _).
1339pack_options_compatible_with_info(Info, PackOptions) :-
1340 findall(Prop, option_info_prop(PackOptions, Prop), Pairs),
1341 dict_create(Dict, _, Pairs),
1342 Dict >:< Info.1352download_plan(_Targets, Plan, Plan, _Options) :- 1353 exclude(installed, Plan, []), 1354 !. 1355download_plan(Targets, Plan0, Plan, Options) :- 1356 confirm(download_plan(Plan0), yes, Options), 1357 maplist(download_from_info(Options), Plan0, Plan1), 1358 plan_unsatisfied_dependencies(Plan1, Deps), 1359 ( Deps == [] 1360 -> Plan = Plan1 1361 ; print_message(informational, pack(new_dependencies(Deps))), 1362 prolog_description(Properties), 1363 query_pack_server(versions(Deps, Properties), Result, []), 1364 ( Result = true(Versions) 1365 -> pack_resolve(Targets, Plan1, Versions, Plan2, Options), 1366 !, 1367 download_plan(Targets, Plan2, Plan, Options) 1368 ; print_message(error, pack(query_failed(Result))), 1369 fail 1370 ) 1371 ).
1378plan_unsatisfied_dependencies(Plan, Deps) :- 1379 phrase(plan_unsatisfied_dependencies(Plan, Plan), Deps). 1380 1381plan_unsatisfied_dependencies([], _) --> 1382 []. 1383plan_unsatisfied_dependencies([Info|Infos], Plan) --> 1384 { Deps = Info.get(requires) }, 1385 plan_unsatisfied_requirements(Deps, Plan), 1386 plan_unsatisfied_dependencies(Infos, Plan). 1387 1388plan_unsatisfied_requirements([], _) --> 1389 []. 1390plan_unsatisfied_requirements([H|T], Plan) --> 1391 { is_prolog_token(H), % Can this fail? 1392 prolog_satisfies(H) 1393 }, 1394 !, 1395 plan_unsatisfied_requirements(T, Plan). 1396plan_unsatisfied_requirements([H|T], Plan) --> 1397 { member(Info, Plan), 1398 ( ( Version = Info.get(version) 1399 -> Provides = @(Info.get(pack), Version) 1400 ; Provides = Info.get(pack) 1401 ) 1402 ; member(Provides, Info.get(provides)) 1403 ), 1404 satisfies_req(Provides, H) 1405 }, !, 1406 plan_unsatisfied_requirements(T, Plan). 1407plan_unsatisfied_requirements([H|T], Plan) --> 1408 [H], 1409 plan_unsatisfied_requirements(T, Plan).
1418build_plan(Plan, Ordered, Options) :-
1419 maplist(decide_autoload_pack(Options), Plan, Plan1),
1420 partition(needs_rebuild_from_info(Options), Plan1, ToBuild, NoBuild),
1421 maplist(attach_from_info(Options), NoBuild),
1422 ( ToBuild == []
1423 -> post_install_autoload(NoBuild),
1424 Ordered = []
1425 ; order_builds(ToBuild, Ordered),
1426 confirm(build_plan(Ordered), yes, Options),
1427 maplist(exec_plan_rebuild_step(Options), Ordered)
1428 ).
1434needs_rebuild_from_info(Options, Info) :-
1435 PackDir = Info.installed,
1436 is_foreign_pack(PackDir, _),
1437 \+ is_built(PackDir, Options).
1446is_built(PackDir, _Options) :-
1447 current_prolog_flag(arch, Arch),
1448 prolog_version_dotted(Version), % Major.Minor.Patch
1449 pack_status_dir(PackDir, built(Arch, Version, _)).
1456order_builds(ToBuild, Ordered) :-
1457 findall(Pack-Dependent, dep_edge(ToBuild, Pack, Dependent), Edges),
1458 maplist(get_dict(pack), ToBuild, Packs),
1459 vertices_edges_to_ugraph(Packs, Edges, Graph),
1460 ugraph_layers(Graph, Layers),
1461 append(Layers, PackNames),
1462 maplist(pack_info_from_name(ToBuild), PackNames, Ordered).1470dep_edge(Infos, Pack, Dependent) :- 1471 member(Info, Infos), 1472 Pack = Info.pack, 1473 member(Dependent, Info.get(dependency_for)), 1474 ( member(DepInfo, Infos), 1475 DepInfo.pack == Dependent 1476 -> true 1477 ). 1478 1479:- det(pack_info_from_name/3). 1480pack_info_from_name(Infos, Pack, Info) :- 1481 member(Info, Infos), 1482 Info.pack == Pack, 1483 !.
1489exec_plan_rebuild_step(Options, Info) :-
1490 print_message(informational, pack(build(Info.pack, Info.installed))),
1491 pack_post_install(Info, Options),
1492 attach_from_info(Options, Info).1498attach_from_info(_Options, Info) :- 1499 Info.get(keep) == true, 1500 !. 1501attach_from_info(Options, Info) :- 1502 ( option(pack_directory(_Parent), Options) 1503 -> pack_attach(Info.installed, [duplicate(replace)]) 1504 ; pack_attach(Info.installed, []) 1505 ).
1515download_from_info(Options, Info0, Info), option(dryrun(true), Options) => 1516 print_term(Info0, [nl(true)]), 1517 Info = Info0. 1518download_from_info(_Options, Info0, Info), installed(Info0) => 1519 Info = Info0. 1520download_from_info(_Options, Info0, Info), 1521 _{upgrade:OldInfo, git:true} :< Info0, 1522 is_git_directory(OldInfo.installed) => 1523 PackDir = OldInfo.installed, 1524 git_checkout_version(PackDir, [commit(Info0.hash)]), 1525 reload_info(PackDir, Info0, Info). 1526download_from_info(Options, Info0, Info), 1527 _{upgrade:OldInfo} :< Info0 => 1528 PackDir = OldInfo.installed, 1529 detach_pack(OldInfo.pack, PackDir), 1530 delete_directory_and_contents(PackDir), 1531 del_dict(upgrade, Info0, _, Info1), 1532 download_from_info(Options, Info1, Info). 1533download_from_info(Options, Info0, Info), 1534 _{url:URL, git:true} :< Info0, \+ have_git => 1535 git_archive_url(URL, Archive, Options), 1536 download_from_info([git_url(URL)|Options], 1537 Info0.put(_{ url:Archive, 1538 git:false, 1539 git_url:URL 1540 }), 1541 Info1), 1542 % restore the hash to register the download. 1543 ( Info1.get(version) == Info0.get(version), 1544 Hash = Info0.get(hash) 1545 -> Info = Info1.put(hash, Hash) 1546 ; Info = Info1 1547 ). 1548download_from_info(Options, Info0, Info), 1549 _{url:URL} :< Info0 => 1550 select_option(pack_directory(Dir), Options, Options1), 1551 select_option(version(_), Options1, Options2, _), 1552 download_info_extra(Info0, InstallOptions, Options2), 1553 pack_download_from_url(URL, Dir, Info0.pack, 1554 [ interactive(false), 1555 pack_dir(PackDir) 1556 | InstallOptions 1557 ]), 1558 reload_info(PackDir, Info0, Info). 1559 1560download_info_extra(Info, [git(true),commit(Hash)|Options], Options) :- 1561 Info.get(git) == true, 1562 !, 1563 Hash = Info.get(commit, 'HEAD'). 1564download_info_extra(Info, [link(true)|Options], Options) :- 1565 Info.get(link) == true, 1566 !. 1567download_info_extra(_, Options, Options). 1568 1569installed(Info) :- 1570 _ = Info.get(installed). 1571 1572detach_pack(Pack, PackDir) :- 1573 ( current_pack(Pack, PackDir) 1574 -> '$pack_detach'(Pack, PackDir) 1575 ; true 1576 ).
1585reload_info(_PackDir, Info, Info) :- 1586 _ = Info.get(installed), % we read it from the package 1587 !. 1588reload_info(PackDir, Info0, Info) :- 1589 local_pack_info(PackDir, Info1), 1590 Info = Info0.put(installed, PackDir) 1591 .put(downloaded, Info0.url) 1592 .put(Info1).
1599work_done(_, _, _, _, Options), 1600 option(silent(true), Options) => 1601 true. 1602work_done(Targets, Plan, Plan, [], _Options) => 1603 convlist(can_upgrade_target(Plan), Targets, CanUpgrade), 1604 ( CanUpgrade == [] 1605 -> pairs_keys(Targets, Packs), 1606 print_message(informational, pack(up_to_date(Packs))) 1607 ; print_message(informational, pack(installed_can_upgrade(CanUpgrade))) 1608 ). 1609work_done(_, _, _, _, _) => 1610 true. 1611 1612can_upgrade_target(Plan, Pack-_, Info) => 1613 member(Info, Plan), 1614 Info.pack == Pack, 1615 !, 1616 _ = Info.get(latest_version).
1623local_packs(Dir, Packs) :- 1624 findall(Pack, pack_in_subdir(Dir, Pack), Packs). 1625 1626pack_in_subdir(Dir, Info) :- 1627 directory_member(Dir, PackDir, 1628 [ file_type(directory), 1629 hidden(false) 1630 ]), 1631 local_pack_info(PackDir, Info). 1632 1633local_pack_info(PackDir, 1634 #{ pack: Pack, 1635 version: Version, 1636 title: Title, 1637 hash: Hash, 1638 url: URL, 1639 git: IsGit, 1640 requires: Requires, 1641 provides: Provides, 1642 conflicts: Conflicts, 1643 installed: PackDir 1644 }) :- 1645 directory_file_path(PackDir, 'pack.pl', MetaFile), 1646 exists_file(MetaFile), 1647 file_base_name(PackDir, DirName), 1648 findall(Term, pack_dir_info(PackDir, _, Term), Info), 1649 option(pack(Pack), Info, DirName), 1650 option(title(Title), Info, '<no title>'), 1651 option(version(Version), Info, '<no version>'), 1652 option(download(URL), Info, '<no download url>'), 1653 findall(Req, member(requires(Req), Info), Requires), 1654 findall(Prv, member(provides(Prv), Info), Provides), 1655 findall(Cfl, member(conflicts(Cfl), Info), Conflicts), 1656 ( have_git, 1657 is_git_directory(PackDir) 1658 -> git_hash(Hash, [directory(PackDir)]), 1659 IsGit = true 1660 ; Hash = '-', 1661 IsGit = false 1662 ). 1663 1664 1665 /******************************* 1666 * PROLOG VERSIONS * 1667 *******************************/
prolog(Dialect, Version)1678prolog_description([prolog(swi(Version))]) :- 1679 prolog_version(Version). 1680 1681prolog_version(Version) :- 1682 current_prolog_flag(version_git, Version), 1683 !. 1684prolog_version(Version) :- 1685 prolog_version_dotted(Version). 1686 1687prolog_version_dotted(Version) :- 1688 current_prolog_flag(version_data, swi(Major, Minor, Patch, _)), 1689 VNumbers = [Major, Minor, Patch], 1690 atomic_list_concat(VNumbers, '.', Version).
1697is_prolog_token(Token), cmp(Token, prolog, _Cmp, _Version) => true. 1698is_prolog_token(prolog:Feature), atom(Feature) => true. 1699is_prolog_token(prolog:Feature), flag_value_feature(Feature, _Flag, _Value) => 1700 true. 1701is_prolog_token(_) => fail.
requires(Token) terms for
library(Lib)1716prolog_satisfies(Token), cmp(Token, prolog, Cmp, ReqVersion) => 1717 prolog_version(CurrentVersion), 1718 cmp_versions(Cmp, CurrentVersion, ReqVersion). 1719prolog_satisfies(prolog:library(Lib)), atom(Lib) => 1720 exists_source(library(Lib)). 1721prolog_satisfies(prolog:Feature), atom(Feature) => 1722 current_prolog_flag(Feature, true). 1723prolog_satisfies(prolog:Feature), flag_value_feature(Feature, Flag, Value) => 1724 current_prolog_flag(Flag, Value). 1725 1726flag_value_feature(Feature, Flag, Value) :- 1727 compound(Feature), 1728 compound_name_arguments(Feature, Flag, [Value]), 1729 atom(Flag). 1730 1731 1732 /******************************* 1733 * INFO * 1734 *******************************/
Requires library(archive), which is lazily loaded when needed.
1748:- if(exists_source(library(archive))). 1749ensure_loaded_archive :- 1750 current_predicate(archive_open/3), 1751 !. 1752ensure_loaded_archive :- 1753 use_module(library(archive)). 1754 1755pack_archive_info(Archive, Pack, [archive_size(Bytes)|Info], Strip) :- 1756 ensure_loaded_archive, 1757 size_file(Archive, Bytes), 1758 setup_call_cleanup( 1759 archive_open(Archive, Handle, []), 1760 ( repeat, 1761 ( archive_next_header(Handle, InfoFile) 1762 -> true 1763 ; !, fail 1764 ) 1765 ), 1766 archive_close(Handle)), 1767 file_base_name(InfoFile, 'pack.pl'), 1768 atom_concat(Prefix, 'pack.pl', InfoFile), 1769 strip_option(Prefix, Pack, Strip), 1770 setup_call_cleanup( 1771 archive_open_entry(Handle, Stream), 1772 read_stream_to_terms(Stream, Info), 1773 close(Stream)), 1774 !, 1775 must_be(ground, Info), 1776 maplist(valid_term(pack_info_term), Info). 1777:- else. 1778pack_archive_info(_, _, _, _) :- 1779 existence_error(library, archive). 1780:- endif. 1781pack_archive_info(_, _, _, _) :- 1782 existence_error(pack_file, 'pack.pl'). 1783 1784strip_option('', _, []) :- !. 1785strip_option('./', _, []) :- !. 1786strip_option(Prefix, Pack, [remove_prefix(Prefix)]) :- 1787 atom_concat(PrefixDir, /, Prefix), 1788 file_base_name(PrefixDir, Base), 1789 ( Base == Pack 1790 -> true 1791 ; pack_version_file(Pack, _, Base) 1792 -> true 1793 ; \+ sub_atom(PrefixDir, _, _, _, /) 1794 ). 1795 1796read_stream_to_terms(Stream, Terms) :- 1797 read(Stream, Term0), 1798 read_stream_to_terms(Term0, Stream, Terms). 1799 1800read_stream_to_terms(end_of_file, _, []) :- !. 1801read_stream_to_terms(Term0, Stream, [Term0|Terms]) :- 1802 read(Stream, Term1), 1803 read_stream_to_terms(Term1, Stream, Terms).
1811pack_git_info(GitDir, Hash, [git(true), installed_size(Bytes)|Info]) :- 1812 exists_directory(GitDir), 1813 !, 1814 git_ls_tree(Entries, [directory(GitDir)]), 1815 git_hash(Hash, [directory(GitDir)]), 1816 maplist(arg(4), Entries, Sizes), 1817 sum_list(Sizes, Bytes), 1818 dir_metadata(GitDir, Info). 1819 1820dir_metadata(GitDir, Info) :- 1821 directory_file_path(GitDir, 'pack.pl', InfoFile), 1822 read_file_to_terms(InfoFile, Info, [encoding(utf8)]), 1823 maplist(valid_term(pack_info_term), Info).
1829download_file_sanity_check(Archive, Pack, Info) :- 1830 info_field(name(PackName), Info), 1831 info_field(version(PackVersion), Info), 1832 pack_version_file(PackFile, FileVersion, Archive), 1833 must_match([Pack, PackName, PackFile], name), 1834 must_match([PackVersion, FileVersion], version). 1835 1836info_field(Field, Info) :- 1837 memberchk(Field, Info), 1838 ground(Field), 1839 !. 1840info_field(Field, _Info) :- 1841 functor(Field, FieldName, _), 1842 print_message(error, pack(missing(FieldName))), 1843 fail. 1844 1845must_match(Values, _Field) :- 1846 sort(Values, [_]), 1847 !. 1848must_match(Values, Field) :- 1849 print_message(error, pack(conflict(Field, Values))), 1850 fail. 1851 1852 1853 /******************************* 1854 * INSTALLATION * 1855 *******************************/
1869prepare_pack_dir(Dir, Options) :- 1870 exists_directory(Dir), 1871 !, 1872 ( empty_directory(Dir) 1873 -> true 1874 ; remove_existing_pack(Dir, Options) 1875 -> make_directory(Dir) 1876 ). 1877prepare_pack_dir(Dir, _) :- 1878 ( read_link(Dir, _, _) 1879 ; access_file(Dir, exist) 1880 ), 1881 !, 1882 delete_file(Dir), 1883 make_directory(Dir). 1884prepare_pack_dir(Dir, _) :- 1885 make_directory(Dir).
1891empty_directory(Dir) :- 1892 \+ ( directory_files(Dir, Entries), 1893 member(Entry, Entries), 1894 \+ special(Entry) 1895 ). 1896 1897special(.). 1898special(..).
upgrade(true) is present. This is used to remove an old installation
before unpacking a new archive, copy or link a directory with the
new contents.1907remove_existing_pack(PackDir, Options) :- 1908 exists_directory(PackDir), 1909 !, 1910 ( ( option(upgrade(true), Options) 1911 ; confirm(remove_existing_pack(PackDir), yes, Options) 1912 ) 1913 -> delete_directory_and_contents(PackDir) 1914 ; print_message(error, pack(directory_exists(PackDir))), 1915 fail 1916 ). 1917remove_existing_pack(_, _).
1933pack_download_from_url(URL, PackTopDir, Pack, Options) :- 1934 option(git(true), Options), 1935 !, 1936 directory_file_path(PackTopDir, Pack, PackDir), 1937 prepare_pack_dir(PackDir, Options), 1938 ( option(branch(Branch), Options) 1939 -> Extra = ['--branch', Branch] 1940 ; Extra = [] 1941 ), 1942 run_process(path(git), [clone, URL, PackDir|Extra], []), 1943 git_checkout_version(PackDir, [update(false)|Options]), 1944 option(pack_dir(PackDir), Options, _). 1945pack_download_from_url(URL0, PackTopDir, Pack, Options) :- 1946 download_url(URL0), 1947 !, 1948 hsts(URL0, URL, Options), 1949 directory_file_path(PackTopDir, Pack, PackDir), 1950 prepare_pack_dir(PackDir, Options), 1951 pack_download_dir(PackTopDir, DownLoadDir), 1952 download_file(URL, Pack, DownloadBase, Options), 1953 directory_file_path(DownLoadDir, DownloadBase, DownloadFile), 1954 ( option(insecure(true), Options, false) 1955 -> TLSOptions = [cert_verify_hook(ssl_verify)] 1956 ; TLSOptions = [] 1957 ), 1958 print_message(informational, pack(download(begin, Pack, URL, DownloadFile))), 1959 setup_call_cleanup( 1960 http_open(URL, In, TLSOptions), 1961 setup_call_cleanup( 1962 open(DownloadFile, write, Out, [type(binary)]), 1963 copy_stream_data(In, Out), 1964 close(Out)), 1965 close(In)), 1966 print_message(informational, pack(download(end, Pack, URL, DownloadFile))), 1967 pack_archive_info(DownloadFile, Pack, Info, _), 1968 ( option(git_url(GitURL), Options) 1969 -> Origin = GitURL % implicit download from git. 1970 ; download_file_sanity_check(DownloadFile, Pack, Info), 1971 Origin = URL 1972 ), 1973 pack_unpack_from_local(DownloadFile, PackTopDir, Pack, PackDir, Options), 1974 pack_assert(PackDir, archive(DownloadFile, Origin)), 1975 option(pack_dir(PackDir), Options, _). 1976pack_download_from_url(URL, PackTopDir, Pack, Options) :- 1977 local_uri_file_name(URL, File), 1978 !, 1979 pack_unpack_from_local(File, PackTopDir, Pack, PackDir, Options), 1980 pack_assert(PackDir, archive(File, URL)), 1981 option(pack_dir(PackDir), Options, _). 1982pack_download_from_url(URL, _PackTopDir, _Pack, _Options) :- 1983 domain_error(url, URL).
'HEAD'. If 'HEAD', get the HEAD of the
explicit (option branch(Branch)), current or default branch. If
the commit is a hash and it is the tip of a branch, checkout
this branch. Else simply checkout the hash.commit('HEAD').2007git_checkout_version(PackDir, Options) :- 2008 option(commit('HEAD'), Options), 2009 option(branch(Branch), Options), 2010 !, 2011 git_ensure_on_branch(PackDir, Branch), 2012 run_process(path(git), ['-C', PackDir, pull], []). 2013git_checkout_version(PackDir, Options) :- 2014 option(commit('HEAD'), Options), 2015 git_current_branch(_, [directory(PackDir)]), 2016 !, 2017 run_process(path(git), ['-C', PackDir, pull], []). 2018git_checkout_version(PackDir, Options) :- 2019 option(commit('HEAD'), Options), 2020 !, 2021 git_default_branch(Branch, [directory(PackDir)]), 2022 git_ensure_on_branch(PackDir, Branch), 2023 run_process(path(git), ['-C', PackDir, pull], []). 2024git_checkout_version(PackDir, Options) :- 2025 option(commit(Hash), Options), 2026 run_process(path(git), ['-C', PackDir, fetch], []), 2027 git_branches(Branches, [contains(Hash), directory(PackDir)]), 2028 git_process_output(['-C', PackDir, 'rev-parse' | Branches], 2029 read_lines_to_atoms(Commits), 2030 []), 2031 nth1(I, Commits, Hash), 2032 nth1(I, Branches, Branch), 2033 !, 2034 git_ensure_on_branch(PackDir, Branch). 2035git_checkout_version(PackDir, Options) :- 2036 option(commit(Hash), Options), 2037 !, 2038 run_process(path(git), ['-C', PackDir, checkout, '--quiet', Hash], []). 2039git_checkout_version(PackDir, Options) :- 2040 option(version(Version), Options), 2041 !, 2042 git_tags(Tags, [directory(PackDir)]), 2043 ( memberchk(Version, Tags) 2044 -> Tag = Version 2045 ; member(Tag, Tags), 2046 sub_atom(Tag, B, _, 0, Version), 2047 sub_atom(Tag, 0, B, _, Prefix), 2048 version_prefix(Prefix) 2049 -> true 2050 ; existence_error(version_tag, Version) 2051 ), 2052 run_process(path(git), ['-C', PackDir, checkout, Tag], []). 2053git_checkout_version(_PackDir, Options) :- 2054 option(fresh(true), Options), 2055 !. 2056git_checkout_version(PackDir, _Options) :- 2057 git_current_branch(_, [directory(PackDir)]), 2058 !, 2059 run_process(path(git), ['-C', PackDir, pull], []). 2060git_checkout_version(PackDir, _Options) :- 2061 git_default_branch(Branch, [directory(PackDir)]), 2062 git_ensure_on_branch(PackDir, Branch), 2063 run_process(path(git), ['-C', PackDir, pull], []).
2069git_ensure_on_branch(PackDir, Branch) :- 2070 git_current_branch(Branch, [directory(PackDir)]), 2071 !. 2072git_ensure_on_branch(PackDir, Branch) :- 2073 run_process(path(git), ['-C', PackDir, checkout, Branch], []). 2074 2075read_lines_to_atoms(Atoms, In) :- 2076 read_line_to_string(In, Line), 2077 ( Line == end_of_file 2078 -> Atoms = [] 2079 ; atom_string(Atom, Line), 2080 Atoms = [Atom|T], 2081 read_lines_to_atoms(T, In) 2082 ). 2083 2084version_prefix(Prefix) :- 2085 atom_codes(Prefix, Codes), 2086 phrase(version_prefix, Codes). 2087 2088version_prefix --> 2089 [C], 2090 { code_type(C, alpha) }, 2091 !, 2092 version_prefix. 2093version_prefix --> 2094 "-". 2095version_prefix --> 2096 "_". 2097version_prefix --> 2098 "".
2105download_file(URL, Pack, File, Options) :- 2106 option(version(Version), Options), 2107 !, 2108 file_name_extension(_, Ext, URL), 2109 format(atom(File), '~w-~w.~w', [Pack, Version, Ext]). 2110download_file(URL, Pack, File, _) :- 2111 file_base_name(URL,Basename), 2112 no_int_file_name_extension(Tag,Ext,Basename), 2113 tag_version(Tag,Version), 2114 !, 2115 format(atom(File0), '~w-~w', [Pack, Version]), 2116 file_name_extension(File0, Ext, File). 2117download_file(URL, _, File, _) :- 2118 file_base_name(URL, File).
2126:- public pack_url_file/2. 2127pack_url_file(URL, FileID) :- 2128 github_release_url(URL, Pack, Version), 2129 !, 2130 download_file(URL, Pack, FileID, [version(Version)]). 2131pack_url_file(URL, FileID) :- 2132 file_base_name(URL, FileID). 2133 2134% ssl_verify(+SSL, +ProblemCert, +AllCerts, +FirstCert, +Error) 2135% 2136% Used if insecure(true) is given to pack_install/2. Accepts any 2137% certificate. 2138 2139:- public ssl_verify/5. 2140ssl_verify(_SSL, 2141 _ProblemCertificate, _AllCertificates, _FirstCertificate, 2142 _Error). 2143 2144pack_download_dir(PackTopDir, DownLoadDir) :- 2145 directory_file_path(PackTopDir, 'Downloads', DownLoadDir), 2146 ( exists_directory(DownLoadDir) 2147 -> true 2148 ; make_directory(DownLoadDir) 2149 ), 2150 ( access_file(DownLoadDir, write) 2151 -> true 2152 ; permission_error(write, directory, DownLoadDir) 2153 ).
ftp:// are also download URLs, but we cannot download
from them.2161download_url(URL) :- 2162 url_scheme(URL, Scheme), 2163 download_scheme(Scheme). 2164 2165url_scheme(URL, Scheme) :- 2166 atom(URL), 2167 uri_components(URL, Components), 2168 uri_data(scheme, Components, Scheme0), 2169 atom(Scheme0), 2170 Scheme = Scheme0. 2171 2172download_scheme(http). 2173download_scheme(https).
insecure(true), which may also be used to disable TLS
certificate checking. Note that the pack integrity is still
protected by its SHA1 hash.2184hsts(URL0, URL, Options) :- 2185 option(insecure(true), Options, false), 2186 !, 2187 URL = URL0. 2188hsts(URL0, URL, _Options) :- 2189 url_scheme(URL0, http), 2190 !, 2191 uri_edit(scheme(https), URL0, URL). 2192hsts(URL, URL, _Options).
2203pack_post_install(Info, Options) :-
2204 Pack = Info.pack,
2205 PackDir = Info.installed,
2206 post_install_foreign(Pack, PackDir, Options),
2207 post_install_autoload(Info),
2208 pack_attach(PackDir, [duplicate(warning)]).2216pack_rebuild :- 2217 forall(current_pack(Pack), 2218 ( print_message(informational, pack(rebuild(Pack))), 2219 pack_rebuild(Pack) 2220 )). 2221 2222pack_rebuild(Pack) :- 2223 current_pack(Pack, PackDir), 2224 !, 2225 post_install_foreign(Pack, PackDir, [rebuild(true)]), 2226 pack_attach(PackDir, [duplicate(replace)]). 2227pack_rebuild(Pack) :- 2228 unattached_pack(Pack, PackDir), 2229 !, 2230 post_install_foreign(Pack, PackDir, [rebuild(true)]), 2231 pack_attach(PackDir, [duplicate(replace)]). 2232pack_rebuild(Pack) :- 2233 existence_error(pack, Pack). 2234 2235unattached_pack(Pack, BaseDir) :- 2236 directory_file_path(Pack, 'pack.pl', PackFile), 2237 absolute_file_name(pack(PackFile), PackPath, 2238 [ access(read), 2239 file_errors(fail) 2240 ]), 2241 file_directory_name(PackPath, BaseDir).
2257post_install_foreign(Pack, PackDir, Options) :- 2258 is_foreign_pack(PackDir, _), 2259 !, 2260 ( pack_info_term(PackDir, pack_version(Version)) 2261 -> true 2262 ; Version = 1 2263 ), 2264 option(rebuild(Rebuild), Options, if_absent), 2265 current_prolog_flag(arch, Arch), 2266 prolog_version_dotted(PrologVersion), 2267 ( Rebuild == if_absent, 2268 foreign_present(PackDir, Arch) 2269 -> print_message(informational, pack(kept_foreign(Pack, Arch))), 2270 ( pack_status_dir(PackDir, built(Arch, _, _)) 2271 -> true 2272 ; pack_assert(PackDir, built(Arch, PrologVersion, downloaded)) 2273 ) 2274 ; BuildSteps0 = [[dependencies], [configure], build, install, [test]], 2275 ( Rebuild == true 2276 -> BuildSteps1 = [distclean|BuildSteps0] 2277 ; BuildSteps1 = BuildSteps0 2278 ), 2279 ( option(test(false), Options) 2280 -> delete(BuildSteps1, [test], BuildSteps2) 2281 ; BuildSteps2 = BuildSteps1 2282 ), 2283 ( option(clean(true), Options) 2284 -> append(BuildSteps2, [[clean]], BuildSteps) 2285 ; BuildSteps = BuildSteps2 2286 ), 2287 build_steps(BuildSteps, PackDir, [pack_version(Version)|Options]), 2288 pack_assert(PackDir, built(Arch, PrologVersion, built)) 2289 ). 2290post_install_foreign(_, _, _).
lib directory for
the current architecture.
2301foreign_present(PackDir, Arch) :-
2302 atomic_list_concat([PackDir, '/lib'], ForeignBaseDir),
2303 exists_directory(ForeignBaseDir),
2304 !,
2305 atomic_list_concat([PackDir, '/lib/', Arch], ForeignDir),
2306 exists_directory(ForeignDir),
2307 current_prolog_flag(shared_object_extension, Ext),
2308 atomic_list_concat([ForeignDir, '/*.', Ext], Pattern),
2309 expand_file_name(Pattern, Files),
2310 Files \== [].2317is_foreign_pack(PackDir, Type) :- 2318 foreign_file(File, Type), 2319 directory_file_path(PackDir, File, Path), 2320 exists_file(Path). 2321 2322foreign_file('CMakeLists.txt', cmake). 2323foreign_file('configure', configure). 2324foreign_file('configure.in', autoconf). 2325foreign_file('configure.ac', autoconf). 2326foreign_file('Makefile.am', automake). 2327foreign_file('Makefile', make). 2328foreign_file('makefile', make). 2329foreign_file('conanfile.txt', conan). 2330foreign_file('conanfile.py', conan). 2331 2332 2333 /******************************* 2334 * AUTOLOAD * 2335 *******************************/
2341post_install_autoload(List), is_list(List) => 2342 maplist(post_install_autoload, List). 2343post_install_autoload(Info), 2344 _{installed:PackDir, autoload:true} :< Info => 2345 directory_file_path(PackDir, prolog, PrologLibDir), 2346 make_library_index(PrologLibDir). 2347post_install_autoload(Info) => 2348 directory_file_path(Info.installed, 'prolog/INDEX.pl', IndexFile), 2349 ( exists_file(IndexFile) 2350 -> E = error(_,_), 2351 print_message(warning, pack(delete_autoload_index(Info.pack, IndexFile))), 2352 catch(delete_file(IndexFile), E, 2353 print_message(warning, E)) 2354 ; true 2355 ).
2362decide_autoload_pack(Options, Info0, Info) :- 2363 is_autoload_pack(Info0.pack, Info0.installed, Options), 2364 !, 2365 Info = Info0.put(autoload, true). 2366decide_autoload_pack(_, Info, Info). 2367 2368is_autoload_pack(_Pack, _PackDir, Options) :- 2369 option(autoload(true), Options), 2370 !. 2371is_autoload_pack(Pack, PackDir, Options) :- 2372 pack_info_term(PackDir, autoload(true)), 2373 confirm(autoload(Pack), no, Options). 2374 2375 2376 /******************************* 2377 * UPGRADE * 2378 *******************************/
pack_install(Pack, [upgrade(true)]).2384pack_upgrade(Pack) :- 2385 pack_install(Pack, [upgrade(true)]). 2386 2387 2388 /******************************* 2389 * REMOVE * 2390 *******************************/
true delete dependencies without asking.2403pack_remove(Pack) :- 2404 pack_remove(Pack, []). 2405 2406pack_remove(Pack, Options) :- 2407 option(dependencies(false), Options), 2408 !, 2409 pack_remove_forced(Pack). 2410pack_remove(Pack, Options) :- 2411 ( dependents(Pack, Deps) 2412 -> ( option(dependencies(true), Options) 2413 -> true 2414 ; confirm_remove(Pack, Deps, Delete, Options) 2415 ), 2416 forall(member(P, Delete), pack_remove_forced(P)) 2417 ; pack_remove_forced(Pack) 2418 ). 2419 2420pack_remove_forced(Pack) :- 2421 catch('$pack_detach'(Pack, BaseDir), 2422 error(existence_error(pack, Pack), _), 2423 fail), 2424 !, 2425 ( read_link(BaseDir, _, Target) 2426 -> What = link(Target) 2427 ; What = directory 2428 ), 2429 print_message(informational, pack(remove(What, BaseDir))), 2430 delete_directory_and_contents(BaseDir). 2431pack_remove_forced(Pack) :- 2432 unattached_pack(Pack, BaseDir), 2433 !, 2434 delete_directory_and_contents(BaseDir). 2435pack_remove_forced(Pack) :- 2436 print_message(informational, error(existence_error(pack, Pack),_)). 2437 2438confirm_remove(Pack, Deps, Delete, Options) :- 2439 print_message(warning, pack(depends(Pack, Deps))), 2440 menu(pack(resolve_remove), 2441 [ [Pack] = remove_only(Pack), 2442 [Pack|Deps] = remove_deps(Pack, Deps), 2443 [] = cancel 2444 ], [], Delete, Options), 2445 Delete \== []. 2446 2447 2448 /******************************* 2449 * PUBLISH * 2450 *******************************/
?- pack_publish('.', []).
Alternatively, an archive file has been uploaded to a public location. In this scenario we can publish the pack using
?- pack_publish(URL, [])
In both scenarios, pack_publish/2 by default creates an isolated environment and installs the package in this directory from the public URL. On success it triggers the pack server to register the URL as a new pack or a new release of a pack.
Packs may also be published using the app pack, e.g.
swipl pack publish .
Options:
true, and Spec is a git managed directory, install using
the remote repo.git tag -s <tag>.git tag -f <tag>.false (default true), perform the installation, but do
not upload to the server. This can be used for testing.true (default), install and build all packages in an
isolated package directory. If false, use other packages
installed for the environment. The latter may be used to
speedup debugging.true (default), clean the destination directory first2503pack_publish(Dir, Options) :- 2504 \+ download_url(Dir), 2505 is_git_directory(Dir), !, 2506 pack_git_info(Dir, _Hash, Metadata), 2507 prepare_repository(Dir, Metadata, Options), 2508 ( memberchk(download(URL), Metadata), 2509 git_url(URL, _) 2510 -> true 2511 ; option(remote(Remote), Options, origin), 2512 git_remote_url(Remote, RemoteURL, [directory(Dir)]), 2513 git_to_https_url(RemoteURL, URL) 2514 ), 2515 memberchk(version(Version), Metadata), 2516 pack_publish_(URL, 2517 [ version(Version) 2518 | Options 2519 ]). 2520pack_publish(Spec, Options) :- 2521 pack_publish_(Spec, Options). 2522 2523pack_publish_(Spec, Options) :- 2524 pack_default_options(Spec, Pack, Options, DefOptions), 2525 option(url(URL), DefOptions), 2526 valid_publish_url(URL, Options), 2527 prepare_build_location(Pack, Dir, Clean, Options), 2528 ( option(register(false), Options) 2529 -> InstallOptions = DefOptions 2530 ; InstallOptions = [publish(Pack)|DefOptions] 2531 ), 2532 call_cleanup(pack_install(Pack, 2533 [ pack(Pack) 2534 | InstallOptions 2535 ]), 2536 cleanup_publish(Clean, Dir)). 2537 2538cleanup_publish(true, Dir) :- 2539 !, 2540 delete_directory_and_contents(Dir). 2541cleanup_publish(_, _). 2542 2543valid_publish_url(URL, Options) :- 2544 option(register(Register), Options, true), 2545 ( Register == false 2546 -> true 2547 ; download_url(URL) 2548 -> true 2549 ; permission_error(publish, pack, URL) 2550 ). 2551 2552prepare_build_location(Pack, Dir, Clean, Options) :- 2553 ( option(pack_directory(Dir), Options) 2554 -> ensure_directory(Dir), 2555 ( option(clean(true), Options, true) 2556 -> delete_directory_contents(Dir) 2557 ; true 2558 ) 2559 ; tmp_file(pack, Dir), 2560 make_directory(Dir), 2561 Clean = true 2562 ), 2563 ( option(isolated(false), Options) 2564 -> detach_pack(Pack, _), 2565 attach_packs(Dir, [search(first)]) 2566 ; attach_packs(Dir, [replace(true)]) 2567 ).
register(false) is provided, this is
a test run and therefore we do not need this. Otherwise we demand
the working directory to be clean, we tag the current commit and
push the current branch.2578prepare_repository(_Dir, _Metadata, Options) :- 2579 option(register(false), Options), 2580 !. 2581prepare_repository(Dir, Metadata, Options) :- 2582 git_dir_must_be_clean(Dir), 2583 git_must_be_on_default_branch(Dir, Options), 2584 tag_git_dir(Dir, Metadata, Action, Options), 2585 confirm(git_push, yes, Options), 2586 run_process(path(git), ['-C', file(Dir), push ], []), 2587 ( Action = push_tag(Tag) 2588 -> run_process(path(git), ['-C', file(Dir), push, origin, Tag ], []) 2589 ; true 2590 ). 2591 2592git_dir_must_be_clean(Dir) :- 2593 git_describe(Description, [directory(Dir)]), 2594 ( sub_atom(Description, _, _, 0, '-DIRTY') 2595 -> print_message(error, pack(git_not_clean(Dir))), 2596 fail 2597 ; true 2598 ). 2599 2600git_must_be_on_default_branch(Dir, Options) :- 2601 ( option(branch(Default), Options) 2602 -> true 2603 ; git_default_branch(Default, [directory(Dir)]) 2604 ), 2605 git_current_branch(Current, [directory(Dir)]), 2606 ( Default == Current 2607 -> true 2608 ; print_message(error, 2609 pack(git_branch_not_default(Dir, Default, Current))), 2610 fail 2611 ).
2620tag_git_dir(Dir, Metadata, Action, Options) :- 2621 memberchk(version(Version), Metadata), 2622 atom_concat('V', Version, Tag), 2623 git_tags(Tags, [directory(Dir)]), 2624 ( memberchk(Tag, Tags) 2625 -> git_tag_is_consistent(Dir, Tag, Action, Options) 2626 ; format(string(Message), 'Release ~w', [Version]), 2627 findall(Opt, git_tag_option(Opt, Options), Argv, 2628 [ '-m', Message, Tag ]), 2629 confirm(git_tag(Tag), yes, Options), 2630 run_process(path(git), ['-C', file(Dir), tag | Argv ], []), 2631 Action = push_tag(Tag) 2632 ). 2633 2634git_tag_option('-s', Options) :- option(sign(true), Options, true). 2635git_tag_option('-f', Options) :- option(force(true), Options, true). 2636 2637git_tag_is_consistent(Dir, Tag, Action, Options) :- 2638 format(atom(TagRef), 'refs/tags/~w', [Tag]), 2639 format(atom(CommitRef), 'refs/tags/~w^{}', [Tag]), 2640 option(remote(Remote), Options, origin), 2641 git_ls_remote(Dir, LocalTags, [tags(true)]), 2642 memberchk(CommitHash-CommitRef, LocalTags), 2643 ( git_hash(CommitHash, [directory(Dir)]) 2644 -> true 2645 ; print_message(error, pack(git_release_tag_not_at_head(Tag))), 2646 fail 2647 ), 2648 memberchk(TagHash-TagRef, LocalTags), 2649 git_ls_remote(Remote, RemoteTags, [tags(true)]), 2650 ( memberchk(RemoteCommitHash-CommitRef, RemoteTags), 2651 memberchk(RemoteTagHash-TagRef, RemoteTags) 2652 -> ( RemoteCommitHash == CommitHash, 2653 RemoteTagHash == TagHash 2654 -> Action = none 2655 ; print_message(error, pack(git_tag_out_of_sync(Tag))), 2656 fail 2657 ) 2658 ; Action = push_tag(Tag) 2659 ).
2667git_to_https_url(URL, URL) :- 2668 download_url(URL), 2669 !. 2670git_to_https_url(GitURL, URL) :- 2671 atom_concat('git@github.com:', Repo, GitURL), 2672 !, 2673 atom_concat('https://github.com/', Repo, URL). 2674git_to_https_url(GitURL, _) :- 2675 print_message(error, pack(git_no_https(GitURL))), 2676 fail. 2677 2678 2679 /******************************* 2680 * PROPERTIES * 2681 *******************************/
README file (if present)TODO file (if present)2704pack_property(Pack, Property) :- 2705 findall(Pack-Property, pack_property_(Pack, Property), List), 2706 member(Pack-Property, List). % make det if applicable 2707 2708pack_property_(Pack, Property) :- 2709 pack_info(Pack, _, Property). 2710pack_property_(Pack, Property) :- 2711 \+ \+ info_file(Property, _), 2712 '$pack':pack(Pack, BaseDir), 2713 access_file(BaseDir, read), 2714 directory_files(BaseDir, Files), 2715 member(File, Files), 2716 info_file(Property, Pattern), 2717 downcase_atom(File, Pattern), 2718 directory_file_path(BaseDir, File, InfoFile), 2719 arg(1, Property, InfoFile). 2720 2721info_file(readme(_), 'readme.txt'). 2722info_file(readme(_), 'readme'). 2723info_file(todo(_), 'todo.txt'). 2724info_file(todo(_), 'todo'). 2725 2726 2727 /******************************* 2728 * VERSION LOGIC * 2729 *******************************/
mypack-1.5.2738pack_version_file(Pack, Version, GitHubRelease) :- 2739 atomic(GitHubRelease), 2740 github_release_url(GitHubRelease, Pack, Version), 2741 !. 2742pack_version_file(Pack, Version, Path) :- 2743 atomic(Path), 2744 file_base_name(Path, File), 2745 no_int_file_name_extension(Base, _Ext, File), 2746 atom_codes(Base, Codes), 2747 ( phrase(pack_version(Pack, Version), Codes), 2748 safe_pack_name(Pack) 2749 -> true 2750 ). 2751 2752no_int_file_name_extension(Base, Ext, File) :- 2753 file_name_extension(Base0, Ext0, File), 2754 \+ atom_number(Ext0, _), 2755 !, 2756 Base = Base0, 2757 Ext = Ext0. 2758no_int_file_name_extension(File, '', File).
2765safe_pack_name(Name) :- 2766 atom_length(Name, Len), 2767 Len >= 3, % demand at least three length 2768 atom_codes(Name, Codes), 2769 maplist(safe_pack_char, Codes), 2770 !. 2771 2772safe_pack_char(C) :- between(0'a, 0'z, C), !. 2773safe_pack_char(C) :- between(0'A, 0'Z, C), !. 2774safe_pack_char(C) :- between(0'0, 0'9, C), !. 2775safe_pack_char(0'_).
2781pack_version(Pack, Version) --> 2782 string(Codes), "-", 2783 version(Parts), 2784 !, 2785 { atom_codes(Pack, Codes), 2786 atomic_list_concat(Parts, '.', Version) 2787 }. 2788 2789version([H|T]) --> 2790 version_part(H), 2791 ( "." 2792 -> version(T) 2793 ; {T=[]} 2794 ). 2795 2796version_part(*) --> "*", !. 2797version_part(Int) --> integer(Int). 2798 2799 2800 /******************************* 2801 * GIT LOGIC * 2802 *******************************/
git program. This could be simple, but Apple
decided to include a fake `/usr/bin/git` that triggers the Xcode
installation. So, if we find git at `/usr/bin/git` we should check
that Xcode is properly enabled. This is the case if xcode-select
-p points at an Xcode installation. Note that if we find git at
some other location, we assume it is installed by the user,
Macports, Homebrew or something else.2814have_git :- 2815 process_which(path(git), GIT), 2816 is_sane_git(GIT). 2817 2818:- if(current_prolog_flag(apple, true)). 2819sane_xcode_path --> 2820 "Xcode.app/Contents". 2821sane_xcode_path --> 2822 "CommandLineTools". 2823 2824is_sane_git('/usr/bin/git') :- 2825 !, 2826 process_which(path('xcode-select'), XSpath), 2827 catch(run_process(XSpath,['-p'],[output(Output),error(_)]), error(_,_), fail), 2828 once(phrase((string(_), sane_xcode_path), Output, _)). 2829:- endif. 2830is_sane_git(_).
2836git_url(URL, Pack) :- 2837 uri_components(URL, Components), 2838 uri_data(scheme, Components, Scheme), 2839 nonvar(Scheme), % must be full URL 2840 uri_data(path, Components, Path), 2841 ( Scheme == git 2842 -> true 2843 ; git_download_scheme(Scheme), 2844 file_name_extension(_, git, Path) 2845 ; git_download_scheme(Scheme), 2846 catch(git_ls_remote(URL, _, [refs(['HEAD']), error(_)]), _, fail) 2847 -> true 2848 ), 2849 file_base_name(Path, PackExt), 2850 ( file_name_extension(Pack, git, PackExt) 2851 -> true 2852 ; Pack = PackExt 2853 ), 2854 ( safe_pack_name(Pack) 2855 -> true 2856 ; domain_error(pack_name, Pack) 2857 ). 2858 2859git_download_scheme(http). 2860git_download_scheme(https).
https:/github.com/<owner>/<pack>/archive/[vV]?<version>.zip'
2869github_release_url(URL, Pack, Version) :- 2870 uri_components(URL, Components), 2871 uri_data(authority, Components, 'github.com'), 2872 uri_data(scheme, Components, Scheme), 2873 download_scheme(Scheme), 2874 uri_data(path, Components, Path), 2875 github_archive_path(Archive,Pack,File), 2876 atomic_list_concat(Archive, /, Path), 2877 file_name_extension(Tag, Ext, File), 2878 github_archive_extension(Ext), 2879 tag_version(Tag, Version), 2880 !. 2881 2882github_archive_path(['',_User,Pack,archive,File],Pack,File). 2883github_archive_path(['',_User,Pack,archive,refs,tags,File],Pack,File). 2884 2885github_archive_extension(tgz). 2886github_archive_extension(zip).
[vV]?int(\.int)*.2893tag_version(Tag, Version) :- 2894 version_tag_prefix(Prefix), 2895 atom_concat(Prefix, Version, Tag), 2896 is_version(Version). 2897 2898version_tag_prefix(v). 2899version_tag_prefix('V'). 2900version_tag_prefix('').
2909git_archive_url(URL, Archive, Options) :- 2910 uri_components(URL, Components), 2911 uri_data(authority, Components, 'github.com'), 2912 uri_data(path, Components, Path), 2913 atomic_list_concat(['', User, RepoGit], /, Path), 2914 $, 2915 remove_git_ext(RepoGit, Repo), 2916 git_archive_version(Version, Options), 2917 atomic_list_concat(['', User, Repo, zip, Version], /, ArchivePath), 2918 uri_edit([ path(ArchivePath), 2919 host('codeload.github.com') 2920 ], 2921 URL, Archive). 2922git_archive_url(URL, _, _) :- 2923 print_message(error, pack(no_git(URL))), 2924 fail. 2925 2926remove_git_ext(RepoGit, Repo) :- 2927 file_name_extension(Repo, git, RepoGit), 2928 !. 2929remove_git_ext(Repo, Repo). 2930 2931git_archive_version(Version, Options) :- 2932 option(commit(Version), Options), 2933 !. 2934git_archive_version(Version, Options) :- 2935 option(branch(Version), Options), 2936 !. 2937git_archive_version(Version, Options) :- 2938 option(version(Version), Options), 2939 !. 2940git_archive_version('HEAD', _). 2941 2942 /******************************* 2943 * QUERY CENTRAL DB * 2944 *******************************/
publish(Pack) that must be
a no-op.publish(Pack) by do_publish(Pack).2959register_downloads(_, Options) :- 2960 option(register(false), Options), 2961 !. 2962register_downloads(_, Options) :- 2963 option(publish(_), Options), 2964 !. 2965register_downloads(Infos, Options) :- 2966 convlist(download_data, Infos, Data), 2967 ( Data == [] 2968 -> true 2969 ; query_pack_server(downloaded(Data), Reply, Options), 2970 ( option(do_publish(Pack), Options) 2971 -> ( member(Info, Infos), 2972 Info.pack == Pack 2973 -> true 2974 ), 2975 ( Reply = true(Actions), 2976 memberchk(Pack-Result, Actions) 2977 -> ( registered(Result) 2978 -> print_message(informational, pack(published(Info, Result))) 2979 ; print_message(error, pack(publish_failed(Info, Result))), 2980 fail 2981 ) 2982 ; print_message(error, pack(publish_failed(Info, false))) 2983 ) 2984 ; true 2985 ) 2986 ). 2987 2988registered(git(_URL)). 2989registered(file(_URL)). 2990 2991publish_download(Infos, Options) :- 2992 select_option(publish(Pack), Options, Options1), 2993 !, 2994 register_downloads(Infos, [do_publish(Pack)|Options1]). 2995publish_download(_Infos, _Options).
download(URL, Hash, Metadata).
Where URL is location of the GIT repository or URL of the download archive. Hash is either the GIT commit hash or the SHA1 of the archive file.
3008download_data(Info, Data), 3009 Info.get(git) == true => % Git clone 3010 Data = download(URL, Hash, Metadata), 3011 URL = Info.get(downloaded), 3012 pack_git_info(Info.installed, Hash, Metadata). 3013download_data(Info, Data), 3014 _{git_url:URL,hash:Hash} :< Info, Hash \== (-) => 3015 Data = download(URL, Hash, Metadata), % Git downloaded as zip 3016 dir_metadata(Info.installed, Metadata). 3017download_data(Info, Data) => % Archive download. 3018 Data = download(URL, Hash, Metadata), 3019 URL = Info.get(downloaded), 3020 download_url(URL), 3021 pack_status_dir(Info.installed, archive(Archive, URL)), 3022 file_sha1(Archive, Hash), 3023 pack_archive_info(Archive, _Pack, Metadata, _).
3030query_pack_server(Query, Result, Options) :- 3031 ( option(server(ServerOpt), Options) 3032 -> server_url(ServerOpt, ServerBase) 3033 ; setting(server, ServerBase), 3034 ServerBase \== '' 3035 ), 3036 atom_concat(ServerBase, query, Server), 3037 format(codes(Data), '~q.~n', Query), 3038 info_level(Informational, Options), 3039 print_message(Informational, pack(contacting_server(Server))), 3040 setup_call_cleanup( 3041 http_open(Server, In, 3042 [ post(codes(application/'x-prolog', Data)), 3043 header(content_type, ContentType) 3044 ]), 3045 read_reply(ContentType, In, Result), 3046 close(In)), 3047 message_severity(Result, Level, Informational), 3048 print_message(Level, pack(server_reply(Result))). 3049 3050server_url(URL0, URL) :- 3051 uri_components(URL0, Components), 3052 uri_data(scheme, Components, Scheme), 3053 var(Scheme), 3054 !, 3055 atom_concat('https://', URL0, URL1), 3056 server_url(URL1, URL). 3057server_url(URL0, URL) :- 3058 uri_components(URL0, Components), 3059 uri_data(path, Components, ''), 3060 !, 3061 uri_edit([path('/pack/')], URL0, URL). 3062server_url(URL, URL). 3063 3064read_reply(ContentType, In, Result) :- 3065 sub_atom(ContentType, 0, _, _, 'application/x-prolog'), 3066 !, 3067 set_stream(In, encoding(utf8)), 3068 read(In, Result). 3069read_reply(ContentType, In, _Result) :- 3070 read_string(In, 500, String), 3071 print_message(error, pack(no_prolog_response(ContentType, String))), 3072 fail. 3073 3074info_level(Level, Options) :- 3075 option(silent(true), Options), 3076 !, 3077 Level = silent. 3078info_level(informational, _). 3079 3080message_severity(true(_), Informational, Informational). 3081message_severity(false, warning, _). 3082message_severity(exception(_), error, _). 3083 3084 3085 /******************************* 3086 * WILDCARD URIs * 3087 *******************************/
3096available_download_versions(URL, Versions, _Options) :- 3097 wildcard_pattern(URL), 3098 github_url(URL, User, Repo), % demands https 3099 !, 3100 findall(Version-VersionURL, 3101 github_version(User, Repo, Version, VersionURL), 3102 Versions). 3103available_download_versions(URL0, Versions, Options) :- 3104 wildcard_pattern(URL0), 3105 !, 3106 hsts(URL0, URL, Options), 3107 file_directory_name(URL, DirURL0), 3108 ensure_slash(DirURL0, DirURL), 3109 print_message(informational, pack(query_versions(DirURL))), 3110 setup_call_cleanup( 3111 http_open(DirURL, In, []), 3112 load_html(stream(In), DOM, 3113 [ syntax_errors(quiet) 3114 ]), 3115 close(In)), 3116 findall(MatchingURL, 3117 absolute_matching_href(DOM, URL, MatchingURL), 3118 MatchingURLs), 3119 ( MatchingURLs == [] 3120 -> print_message(warning, pack(no_matching_urls(URL))) 3121 ; true 3122 ), 3123 versioned_urls(MatchingURLs, VersionedURLs), 3124 sort_version_pairs(VersionedURLs, Versions), 3125 print_message(informational, pack(found_versions(Versions))). 3126available_download_versions(URL, [Version-URL], _Options) :- 3127 ( pack_version_file(_Pack, Version0, URL) 3128 -> Version = Version0 3129 ; Version = '0.0.0' 3130 ).
3136sort_version_pairs(Pairs, Sorted) :- 3137 map_list_to_pairs(version_pair_sort_key_, Pairs, Keyed), 3138 sort(1, @>=, Keyed, SortedKeyed), 3139 pairs_values(SortedKeyed, Sorted). 3140 3141version_pair_sort_key_(Version-_Data, Key) :- 3142 version_sort_key(Version, Key). 3143 3144version_sort_key(Version, Key) :- 3145 split_string(Version, ".", "", Parts), 3146 maplist(number_string, Key, Parts), 3147 !. 3148version_sort_key(Version, _) :- 3149 domain_error(version, Version).
3155github_url(URL, User, Repo) :-
3156 uri_components(URL, uri_components(https,'github.com',Path,_,_)),
3157 atomic_list_concat(['',User,Repo|_], /, Path).3165github_version(User, Repo, Version, VersionURI) :- 3166 atomic_list_concat(['',repos,User,Repo,tags], /, Path1), 3167 uri_components(ApiUri, uri_components(https,'api.github.com',Path1,_,_)), 3168 setup_call_cleanup( 3169 http_open(ApiUri, In, 3170 [ request_header('Accept'='application/vnd.github.v3+json') 3171 ]), 3172 json_read_dict(In, Dicts), 3173 close(In)), 3174 member(Dict, Dicts), 3175 atom_string(Tag, Dict.name), 3176 tag_version(Tag, Version), 3177 atom_string(VersionURI, Dict.zipball_url). 3178 3179wildcard_pattern(URL) :- sub_atom(URL, _, _, _, *). 3180wildcard_pattern(URL) :- sub_atom(URL, _, _, _, ?). 3181 3182ensure_slash(Dir, DirS) :- 3183 ( sub_atom(Dir, _, _, 0, /) 3184 -> DirS = Dir 3185 ; atom_concat(Dir, /, DirS) 3186 ). 3187 3188remove_slash(Dir0, Dir) :- 3189 Dir0 \== '/', 3190 atom_concat(Dir1, /, Dir0), 3191 !, 3192 remove_slash(Dir1, Dir). 3193remove_slash(Dir, Dir). 3194 3195absolute_matching_href(DOM, Pattern, Match) :- 3196 xpath(DOM, //a(@href), HREF), 3197 uri_normalized(HREF, Pattern, Match), 3198 wildcard_match(Pattern, Match). 3199 3200versioned_urls([], []). 3201versioned_urls([H|T0], List) :- 3202 file_base_name(H, File), 3203 ( pack_version_file(_Pack, Version, File) 3204 -> List = [Version-H|T] 3205 ; List = T 3206 ), 3207 versioned_urls(T0, T). 3208 3209 3210 /******************************* 3211 * DEPENDENCIES * 3212 *******************************/
3220pack_provides(Pack, Pack@Version) :- 3221 current_pack(Pack), 3222 once(pack_info(Pack, version, version(Version))). 3223pack_provides(Pack, Provides) :- 3224 findall(Prv, pack_info(Pack, dependency, provides(Prv)), PrvList), 3225 member(Provides, PrvList). 3226 3227pack_requires(Pack, Requires) :- 3228 current_pack(Pack), 3229 findall(Req, pack_info(Pack, dependency, requires(Req)), ReqList), 3230 member(Requires, ReqList). 3231 3232pack_conflicts(Pack, Conflicts) :- 3233 current_pack(Pack), 3234 findall(Cfl, pack_info(Pack, dependency, conflicts(Cfl)), CflList), 3235 member(Conflicts, CflList).
3242pack_depends_on(Pack, Dependency) :- 3243 ground(Pack), 3244 !, 3245 pack_requires(Pack, Requires), 3246 \+ is_prolog_token(Requires), 3247 pack_provides(Dependency, Provides), 3248 satisfies_req(Provides, Requires). 3249pack_depends_on(Pack, Dependency) :- 3250 ground(Dependency), 3251 !, 3252 pack_provides(Dependency, Provides), 3253 pack_requires(Pack, Requires), 3254 satisfies_req(Provides, Requires). 3255pack_depends_on(Pack, Dependency) :- 3256 current_pack(Pack), 3257 pack_depends_on(Pack, Dependency).
3264dependents(Pack, Deps) :- 3265 setof(Dep, dependent(Pack, Dep, []), Deps). 3266 3267dependent(Pack, Dep, Seen) :- 3268 pack_depends_on(Dep0, Pack), 3269 \+ memberchk(Dep0, Seen), 3270 ( Dep = Dep0 3271 ; dependent(Dep0, Dep, [Dep0|Seen]) 3272 ).
3278validate_dependencies :- 3279 setof(Issue, pack_dependency_issue(_, Issue), Issues), 3280 !, 3281 print_message(warning, pack(dependency_issues(Issues))). 3282validate_dependencies.
3294pack_dependency_issue(Pack, Issue) :- 3295 current_pack(Pack), 3296 pack_dependency_issue_(Pack, Issue). 3297 3298pack_dependency_issue_(Pack, unsatisfied(Pack, Requires)) :- 3299 pack_requires(Pack, Requires), 3300 ( is_prolog_token(Requires) 3301 -> \+ prolog_satisfies(Requires) 3302 ; \+ ( pack_provides(_, Provides), 3303 satisfies_req(Provides, Requires) ) 3304 ). 3305pack_dependency_issue_(Pack, conflicts(Pack, Conflicts)) :- 3306 pack_conflicts(Pack, Conflicts), 3307 ( is_prolog_token(Conflicts) 3308 -> prolog_satisfies(Conflicts) 3309 ; pack_provides(_, Provides), 3310 satisfies_req(Provides, Conflicts) 3311 ). 3312 3313 3314 /******************************* 3315 * RECORD PACK FACTS * 3316 *******************************/
built if we built it or downloaded if it was downloaded.true, pack was installed as dependency.3332pack_assert(PackDir, Fact) :- 3333 must_be(ground, Fact), 3334 findall(Term, pack_status_dir(PackDir, Term), Facts0), 3335 update_facts(Facts0, Fact, Facts), 3336 OpenOptions = [encoding(utf8), lock(exclusive)], 3337 status_file(PackDir, StatusFile), 3338 ( Facts == Facts0 3339 -> true 3340 ; Facts0 \== [], 3341 append(Facts0, New, Facts) 3342 -> setup_call_cleanup( 3343 open(StatusFile, append, Out, OpenOptions), 3344 maplist(write_fact(Out), New), 3345 close(Out)) 3346 ; setup_call_cleanup( 3347 open(StatusFile, write, Out, OpenOptions), 3348 ( write_facts_header(Out), 3349 maplist(write_fact(Out), Facts) 3350 ), 3351 close(Out)) 3352 ). 3353 3354update_facts([], Fact, [Fact]) :- 3355 !. 3356update_facts([H|T], Fact, [Fact|T]) :- 3357 general_pack_fact(Fact, GenFact), 3358 general_pack_fact(H, GenTerm), 3359 GenFact =@= GenTerm, 3360 !. 3361update_facts([H|T0], Fact, [H|T]) :- 3362 update_facts(T0, Fact, T). 3363 3364general_pack_fact(built(Arch, _Version, _How), General) => 3365 General = built(Arch, _, _). 3366general_pack_fact(Term, General), compound(Term) => 3367 compound_name_arity(Term, Name, Arity), 3368 compound_name_arity(General, Name, Arity). 3369general_pack_fact(Term, General) => 3370 General = Term. 3371 3372write_facts_header(Out) :- 3373 format(Out, '% Fact status file. Managed by package manager.~n', []). 3374 3375write_fact(Out, Term) :- 3376 format(Out, '~q.~n', [Term]).
status.db.3384pack_status(Pack, Fact) :- 3385 current_pack(Pack, PackDir), 3386 pack_status_dir(PackDir, Fact). 3387 3388pack_status_dir(PackDir, Fact) :- 3389 det_if(ground(Fact), pack_status_(PackDir, Fact)). 3390 3391pack_status_(PackDir, Fact) :- 3392 status_file(PackDir, StatusFile), 3393 catch(term_in_file(valid_term(pack_status_term), StatusFile, Fact), 3394 error(existence_error(source_sink, StatusFile), _), 3395 fail). 3396 3397pack_status_term(built(atom, version, oneof([built,downloaded]))). 3398pack_status_term(automatic(boolean)). 3399pack_status_term(archive(atom, atom)).
3409update_automatic(Info) :- 3410 _ = Info.get(dependency_for), 3411 \+ pack_status(Info.installed, automatic(_)), 3412 !, 3413 pack_assert(Info.installed, automatic(true)). 3414update_automatic(Info) :- 3415 pack_assert(Info.installed, automatic(false)). 3416 3417status_file(PackDir, StatusFile) :- 3418 directory_file_path(PackDir, 'status.db', StatusFile). 3419 3420 /******************************* 3421 * USER INTERACTION * 3422 *******************************/ 3423 3424:- multifile prolog:message//1.
3428menu(_Question, _Alternatives, Default, Selection, Options) :- 3429 option(interactive(false), Options), 3430 !, 3431 Selection = Default. 3432menu(Question, Alternatives, Default, Selection, _) :- 3433 length(Alternatives, N), 3434 between(1, 5, _), 3435 print_message(query, Question), 3436 print_menu(Alternatives, Default, 1), 3437 print_message(query, pack(menu(select))), 3438 read_selection(N, Choice), 3439 !, 3440 ( Choice == default 3441 -> Selection = Default 3442 ; nth1(Choice, Alternatives, Selection=_) 3443 -> true 3444 ). 3445 ([], _, _). 3447print_menu([Value=Label|T], Default, I) :- 3448 ( Value == Default 3449 -> print_message(query, pack(menu(default_item(I, Label)))) 3450 ; print_message(query, pack(menu(item(I, Label)))) 3451 ), 3452 I2 is I + 1, 3453 print_menu(T, Default, I2). 3454 3455read_selection(Max, Choice) :- 3456 get_single_char(Code), 3457 ( answered_default(Code) 3458 -> Choice = default 3459 ; code_type(Code, digit(Choice)), 3460 between(1, Max, Choice) 3461 -> true 3462 ; print_message(warning, pack(menu(reply(1,Max)))), 3463 fail 3464 ).
3472confirm(_Question, Default, Options) :- 3473 Default \== none, 3474 option(interactive(false), Options, true), 3475 !, 3476 Default == yes. 3477confirm(Question, Default, _) :- 3478 between(1, 5, _), 3479 print_message(query, pack(confirm(Question, Default))), 3480 read_yes_no(YesNo, Default), 3481 !, 3482 format(user_error, '~N', []), 3483 YesNo == yes. 3484 3485read_yes_no(YesNo, Default) :- 3486 get_single_char(Code), 3487 code_yes_no(Code, Default, YesNo), 3488 !. 3489 3490code_yes_no(0'y, _, yes). 3491code_yes_no(0'Y, _, yes). 3492code_yes_no(0'n, _, no). 3493code_yes_no(0'N, _, no). 3494code_yes_no(_, none, _) :- !, fail. 3495code_yes_no(C, Default, Default) :- 3496 answered_default(C). 3497 3498answered_default(0'\r). 3499answered_default(0'\n). 3500answered_default(0'\s). 3501 3502 3503 /******************************* 3504 * MESSAGES * 3505 *******************************/ 3506 3507:- multifile prolog:message//1. 3508 3509prologmessage(pack(Message)) --> 3510 message(Message). 3511 3512:- discontiguous 3513 message//1, 3514 label//1. 3515 3516message(invalid_term(pack_info_term, Term)) --> 3517 [ 'Invalid package meta data: ~q'-[Term] ]. 3518message(invalid_term(pack_status_term, Term)) --> 3519 [ 'Invalid package status data: ~q'-[Term] ]. 3520message(directory_exists(Dir)) --> 3521 [ 'Package target directory exists and is not empty:', nl, 3522 '\t~q'-[Dir] 3523 ]. 3524message(already_installed(pack(Pack, Version))) --> 3525 [ 'Pack `~w'' is already installed @~w'-[Pack, Version] ]. 3526message(already_installed(Pack)) --> 3527 [ 'Pack `~w'' is already installed. Package info:'-[Pack] ]. 3528message(kept_foreign(Pack, Arch)) --> 3529 [ 'Found foreign libraries for architecture '-[], 3530 ansi(code, '~q', [Arch]), nl, 3531 'Use ', ansi(code, '?- pack_rebuild(~q).', [Pack]), 3532 ' to rebuild from sources'-[] 3533 ]. 3534message(no_pack_installed(Pack)) --> 3535 [ 'No pack ~q installed. Use ?- pack_list(Pattern) to search'-[Pack] ]. 3536message(dependency_issues(Issues)) --> 3537 [ 'The current set of packs has dependency issues:', nl ], 3538 dep_issues(Issues). 3539message(depends(Pack, Deps)) --> 3540 [ 'The following packs depend on `~w\':'-[Pack], nl ], 3541 pack_list(Deps). 3542message(remove(link(To), PackDir)) --> 3543 [ 'Removing ', url(PackDir), nl, ' as link to ', url(To) ]. 3544message(remove(directory, PackDir)) --> 3545 [ 'Removing ~q and contents'-[PackDir] ]. 3546message(remove_existing_pack(PackDir)) --> 3547 [ 'Remove old installation in ~q'-[PackDir] ]. 3548message(delete_autoload_index(Pack, Index)) --> 3549 [ 'Pack ' ], msg_pack(Pack), [ ': deleting autoload index ', url(Index) ]. 3550message(download_plan(Plan)) --> 3551 [ ansi(bold, 'Installation plan:', []), nl ], 3552 install_plan(Plan, Actions), 3553 install_label(Actions). 3554message(build_plan(Plan)) --> 3555 [ ansi(bold, 'The following packs have post install scripts:', []), nl ], 3556 msg_build_plan(Plan), 3557 [ nl, ansi(bold, 'Run scripts?', []) ]. 3558message(autoload(Pack)) --> 3559 [ 'Pack ' ], msg_pack(Pack), 3560 [ ' prefers to be added as autoload library', 3561 nl, ansi(bold, 'Allow?', []) 3562 ]. 3563message(no_meta_data(BaseDir)) --> 3564 [ 'Cannot find pack.pl inside directory ~q. Not a package?'-[BaseDir] ]. 3565message(search_no_matches(Name)) --> 3566 [ 'Search for "~w", returned no matching packages'-[Name] ]. 3567message(rebuild(Pack)) --> 3568 [ 'Checking pack "~w" for rebuild ...'-[Pack] ]. 3569message(up_to_date([Pack])) --> 3570 !, 3571 [ 'Pack ' ], msg_pack(Pack), [' is up-to-date' ]. 3572message(up_to_date(Packs)) --> 3573 [ 'Packs ' ], sequence(msg_pack, [', '], Packs), [' are up-to-date' ]. 3574message(installed_can_upgrade(List)) --> 3575 sequence(msg_can_upgrade_target, [nl], List). 3576message(new_dependencies(Deps)) --> 3577 [ 'Found new dependencies after downloading (~p).'-[Deps], nl ]. 3578message(query_versions(URL)) --> 3579 [ 'Querying "~w" to find new versions ...'-[URL] ]. 3580message(no_matching_urls(URL)) --> 3581 [ 'Could not find any matching URL: ~q'-[URL] ]. 3582message(found_versions([Latest-_URL|More])) --> 3583 { length(More, Len) }, 3584 [ ' Latest version: ~w (~D older)'-[Latest, Len] ]. 3585message(build(Pack, PackDir)) --> 3586 [ ansi(bold, 'Building pack ~w in directory ~w', [Pack, PackDir]) ]. 3587message(contacting_server(Server)) --> 3588 [ 'Contacting server at ~w ...'-[Server], flush ]. 3589message(server_reply(true(_))) --> 3590 [ at_same_line, ' ok'-[] ]. 3591message(server_reply(false)) --> 3592 [ at_same_line, ' done'-[] ]. 3593message(server_reply(exception(E))) --> 3594 [ 'Server reported the following error:'-[], nl ], 3595 '$messages':translate_message(E). 3596message(cannot_create_dir(Alias)) --> 3597 { findall(PackDir, 3598 absolute_file_name(Alias, PackDir, [solutions(all)]), 3599 PackDirs0), 3600 sort(PackDirs0, PackDirs) 3601 }, 3602 [ 'Cannot find a place to create a package directory.'-[], 3603 'Considered:'-[] 3604 ], 3605 candidate_dirs(PackDirs). 3606message(conflict(version, [PackV, FileV])) --> 3607 ['Version mismatch: pack.pl: '-[]], msg_version(PackV), 3608 [', file claims version '-[]], msg_version(FileV). 3609message(conflict(name, [PackInfo, FileInfo])) --> 3610 ['Pack ~w mismatch: pack.pl: ~p'-[PackInfo]], 3611 [', file claims ~w: ~p'-[FileInfo]]. 3612message(no_prolog_response(ContentType, String)) --> 3613 [ 'Expected Prolog response. Got content of type ~p'-[ContentType], nl, 3614 '~s'-[String] 3615 ]. 3616message(download(begin, Pack, _URL, _DownloadFile)) --> 3617 [ 'Downloading ' ], msg_pack(Pack), [ ' ... ', flush ]. 3618message(download(end, _, _, File)) --> 3619 { size_file(File, Bytes) }, 3620 [ at_same_line, '~D bytes'-[Bytes] ]. 3621message(no_git(URL)) --> 3622 [ 'Cannot install from git repository ', url(URL), '.', nl, 3623 'Cannot find git program and do not know how to download the code', nl, 3624 'from this git service. Please install git and retry.' 3625 ]. 3626message(git_no_https(GitURL)) --> 3627 [ 'Do not know how to get an HTTP(s) URL for ', url(GitURL) ]. 3628message(git_branch_not_default(Dir, Default, Current)) --> 3629 [ 'GIT current branch on ', url(Dir), ' is not default.', nl, 3630 ' Current branch: ', ansi(code, '~w', [Current]), 3631 ' default: ', ansi(code, '~w', [Default]) 3632 ]. 3633message(git_not_clean(Dir)) --> 3634 [ 'GIT working directory is dirty: ', url(Dir), nl, 3635 'Your repository must be clean before publishing.' 3636 ]. 3637message(git_push) --> 3638 [ 'Push release to GIT origin?' ]. 3639message(git_tag(Tag)) --> 3640 [ 'Tag repository with release tag ', ansi(code, '~w', [Tag]) ]. 3641message(git_release_tag_not_at_head(Tag)) --> 3642 [ 'Release tag ', ansi(code, '~w', [Tag]), ' is not at HEAD.', nl, 3643 'If you want to update the tag, please run ', 3644 ansi(code, 'git tag -d ~w', [Tag]) 3645 ]. 3646message(git_tag_out_of_sync(Tag)) --> 3647 [ 'Release tag ', ansi(code, '~w', [Tag]), 3648 ' differs from this tag at the origin' 3649 ]. 3650 3651message(published(Info, At)) --> 3652 [ 'Published pack ' ], msg_pack(Info), msg_info_version(Info), 3653 [' to be installed from '], 3654 msg_published_address(At). 3655message(publish_failed(Info, Reason)) --> 3656 [ 'Pack ' ], msg_pack(Info), [ ' at version ~w'-[Info.version] ], 3657 msg_publish_failed(Reason). 3658 3659msg_publish_failed(throw(error(permission_error(register, 3660 pack(_),_URL),_))) --> 3661 [ ' is already registered with a different URL']. 3662msg_publish_failed(download) --> 3663 [' was already published?']. 3664msg_publish_failed(Status) --> 3665 [ ' failed for unknown reason (~p)'-[Status] ]. 3666 3667msg_published_address(git(URL)) --> 3668 msg_url(URL, _). 3669msg_published_address(file(URL)) --> 3670 msg_url(URL, _). 3671 3672candidate_dirs([]) --> []. 3673candidate_dirs([H|T]) --> [ nl, ' ~w'-[H] ], candidate_dirs(T). 3674 % Questions 3675message(resolve_remove) --> 3676 [ nl, 'Please select an action:', nl, nl ]. 3677message(create_pack_dir) --> 3678 [ nl, 'Create directory for packages', nl ]. 3679message(menu(item(I, Label))) --> 3680 [ '~t(~d)~6| '-[I] ], 3681 label(Label). 3682message(menu(default_item(I, Label))) --> 3683 [ '~t(~d)~6| * '-[I] ], 3684 label(Label). 3685message(menu(select)) --> 3686 [ nl, 'Your choice? ', flush ]. 3687message(confirm(Question, Default)) --> 3688 message(Question), 3689 confirm_default(Default), 3690 [ flush ]. 3691message(menu(reply(Min,Max))) --> 3692 ( { Max =:= Min+1 } 3693 -> [ 'Please enter ~w or ~w'-[Min,Max] ] 3694 ; [ 'Please enter a number between ~w and ~w'-[Min,Max] ] 3695 ). 3696 3697 % support predicates 3698dep_issues(Issues) --> 3699 sequence(dep_issue, [nl], Issues). 3700 3701dep_issue(unsatisfied(Pack, Requires)) --> 3702 [ ' - Pack ' ], msg_pack(Pack), [' requires ~p'-[Requires]]. 3703dep_issue(conflicts(Pack, Conflict)) --> 3704 [ ' - Pack ' ], msg_pack(Pack), [' conflicts with ~p'-[Conflict]].
3711install_label([link]) --> 3712 !, 3713 [ ansi(bold, 'Activate pack?', []) ]. 3714install_label([unpack]) --> 3715 !, 3716 [ ansi(bold, 'Unpack archive?', []) ]. 3717install_label(_) --> 3718 [ ansi(bold, 'Download packs?', []) ]. 3719 3720 3721install_plan(Plan, Actions) --> 3722 install_plan(Plan, Actions, Sec), 3723 sec_warning(Sec). 3724 3725install_plan([], [], _) --> 3726 []. 3727install_plan([H|T], [AH|AT], Sec) --> 3728 install_step(H, AH, Sec), [nl], 3729 install_plan(T, AT, Sec). 3730 3731install_step(Info, keep, _Sec) --> 3732 { Info.get(keep) == true }, 3733 !, 3734 [ ' Keep ' ], msg_pack(Info), [ ' at version ~w'-[Info.version] ], 3735 msg_can_upgrade(Info). 3736install_step(Info, Action, Sec) --> 3737 { From = Info.get(upgrade), 3738 VFrom = From.version, 3739 VTo = Info.get(version), 3740 ( cmp_versions(>=, VTo, VFrom) 3741 -> Label = ansi(bold, ' Upgrade ', []) 3742 ; Label = ansi(warning, ' Downgrade ', []) 3743 ) 3744 }, 3745 [ Label ], msg_pack(Info), 3746 [ ' from version ~w to ~w'- [From.version, Info.get(version)] ], 3747 install_from(Info, Action, Sec). 3748install_step(Info, Action, Sec) --> 3749 { _From = Info.get(upgrade) }, 3750 [ ' Upgrade ' ], msg_pack(Info), 3751 install_from(Info, Action, Sec). 3752install_step(Info, Action, Sec) --> 3753 { Dep = Info.get(dependency_for) }, 3754 [ ' Install ' ], msg_pack(Info), 3755 [ ' at version ~w as dependency for '-[Info.version], 3756 ansi(code, '~w', [Dep]) 3757 ], 3758 install_from(Info, Action, Sec), 3759 msg_downloads(Info). 3760install_step(Info, Action, Sec) --> 3761 { Info.get(commit) == 'HEAD' }, 3762 !, 3763 [ ' Install ' ], msg_pack(Info), [ ' at current GIT HEAD'-[] ], 3764 install_from(Info, Action, Sec), 3765 msg_downloads(Info). 3766install_step(Info, link, _Sec) --> 3767 { Info.get(link) == true, 3768 uri_file_name(Info.get(url), Dir) 3769 }, 3770 !, 3771 [ ' Install ' ], msg_pack(Info), [ ' as symlink to ', url(Dir) ]. 3772install_step(Info, Action, Sec) --> 3773 [ ' Install ' ], msg_pack(Info), [ ' at version ~w'-[Info.get(version)] ], 3774 install_from(Info, Action, Sec), 3775 msg_downloads(Info). 3776install_step(Info, Action, Sec) --> 3777 [ ' Install ' ], msg_pack(Info), 3778 install_from(Info, Action, Sec), 3779 msg_downloads(Info). 3780 3781install_from(Info, download, Sec) --> 3782 { download_url(Info.url) }, 3783 !, 3784 [ ' from ' ], msg_url(Info.url, Sec). 3785install_from(Info, unpack, Sec) --> 3786 [ ' from ' ], msg_url(Info.url, Sec). 3787 3788msg_url(URL, unsafe) --> 3789 { atomic(URL), 3790 atom_concat('http://', Rest, URL) 3791 }, 3792 [ ansi(error, '~w', ['http://']), '~w'-[Rest] ]. 3793msg_url(URL, _) --> 3794 [ url(URL) ]. 3795 3796sec_warning(Sec) --> 3797 { var(Sec) }, 3798 !. 3799sec_warning(unsafe) --> 3800 [ ansi(warning, ' WARNING: The installation plan includes downloads \c 3801 from insecure HTTP servers.', []), nl 3802 ]. 3803 3804msg_downloads(Info) --> 3805 { Downloads = Info.get(all_downloads), 3806 Downloads > 0 3807 }, 3808 [ ansi(comment, ' (downloaded ~D times)', [Downloads]) ], 3809 !. 3810msg_downloads(_) --> 3811 []. 3812 3813msg_pack(Pack) --> 3814 { atom(Pack) }, 3815 !, 3816 [ ansi(code, '~w', [Pack]) ]. 3817msg_pack(Info) --> 3818 msg_pack(Info.pack). 3819 3820msg_info_version(Info) --> 3821 [ ansi(code, '@~w', [Info.get(version)]) ], 3822 !. 3823msg_info_version(_Info) --> 3824 [].
3830msg_build_plan(Plan) --> 3831 sequence(build_step, [nl], Plan). 3832 3833build_step(Info) --> 3834 [ ' Build ' ], msg_pack(Info), [' in directory ', url(Info.installed) ]. 3835 3836msg_can_upgrade_target(Info) --> 3837 [ ' Pack ' ], msg_pack(Info), 3838 [ ' is installed at version ~w'-[Info.version] ], 3839 msg_can_upgrade(Info). 3840 3841pack_list([]) --> []. 3842pack_list([H|T]) --> 3843 [ ' - Pack ' ], msg_pack(H), [nl], 3844 pack_list(T). 3845 3846label(remove_only(Pack)) --> 3847 [ 'Only remove package ~w (break dependencies)'-[Pack] ]. 3848label(remove_deps(Pack, Deps)) --> 3849 { length(Deps, Count) }, 3850 [ 'Remove package ~w and ~D dependencies'-[Pack, Count] ]. 3851label(create_dir(Dir)) --> 3852 [ '~w'-[Dir] ]. 3853label(install_from(git(URL))) --> 3854 !, 3855 [ 'GIT repository at ~w'-[URL] ]. 3856label(install_from(URL)) --> 3857 [ '~w'-[URL] ]. 3858label(cancel) --> 3859 [ 'Cancel' ]. 3860 3861confirm_default(yes) --> 3862 [ ' Y/n? ' ]. 3863confirm_default(no) --> 3864 [ ' y/N? ' ]. 3865confirm_default(none) --> 3866 [ ' y/n? ' ]. 3867 3868msg_version(Version) --> 3869 [ '~w'-[Version] ]. 3870 3871msg_can_upgrade(Info) --> 3872 { Latest = Info.get(latest_version) }, 3873 [ ansi(warning, ' (can be upgraded to ~w)', [Latest]) ]. 3874msg_can_upgrade(_) --> 3875 []. 3876 3877 3878 /******************************* 3879 * MISC * 3880 *******************************/ 3881 3882local_uri_file_name(URL, FileName) :- 3883 uri_file_name(URL, FileName), 3884 !. 3885local_uri_file_name(URL, FileName) :- 3886 uri_components(URL, Components), 3887 uri_data(scheme, Components, File), File == file, 3888 uri_data(authority, Components, FileNameEnc), 3889 uri_data(path, Components, ''), 3890 uri_encoded(path, FileName, FileNameEnc). 3891 3892det_if(Cond, Goal) :- 3893 ( 3894 -> , 3895 ! 3896 ; 3897 ). 3898 3899member_nonvar(_, Var) :- 3900 var(Var), 3901 !, 3902 fail. 3903member_nonvar(E, [E|_]). 3904member_nonvar(E, [_|T]) :- 3905 member_nonvar(E, T)
A package manager for Prolog
The library(prolog_pack) provides the SWI-Prolog package manager. This library lets you inspect installed packages, install packages, remove packages, etc. This library complemented by the built-in predicates such as attach_packs/2 that makes installed packages available as libraries.
The important functionality of this library is encapsulated in the app
pack. For help, run*/