Skip to content

Commit

Permalink
ADDED: swipl pack rebuild [--dir=dir] [pack ...]
Browse files Browse the repository at this point in the history
  • Loading branch information
JanWielemaker committed Dec 21, 2024
1 parent 8261b0f commit 5ee1ee7
Showing 1 changed file with 24 additions and 4 deletions.
28 changes: 24 additions & 4 deletions app/pack.pl
Original file line number Diff line number Diff line change
Expand Up @@ -38,6 +38,7 @@
:- use_module(library(apply)).
:- use_module(library(strings)).
:- use_module(library(dcg/basics)).
:- use_module(library(lists)).

:- initialization(main, main).

Expand All @@ -63,6 +64,9 @@
pack(install, Argv) =>
pack_install:argv_options(Argv, Pos, Options),
cli_pack_install(Pos, Options).
pack(rebuild, Argv) =>
pack_rebuild:argv_options(Argv, Pos, Options),
cli_pack_rebuild(Pos, Options).
pack(remove, Argv) =>
pack_remove:argv_options(Argv, Pos, Options),
cli_pack_remove(Pos, Options).
Expand All @@ -76,12 +80,13 @@
pack(_, _) =>
argv_usage(debug).

pack_command(list, "List packages").
pack_command(find, "Find packages").
pack_command(list, "List packs").
pack_command(find, "Find packs").
pack_command(search, "Alias for `find`").
pack_command(info, "Print info on a pack").
pack_command(install, "Install or upgrade a package").
pack_command(remove, "Uninstall a package").
pack_command(install, "Install or upgrade a pack").
pack_command(rebuild, "Recompile foreign parts for a pack").
pack_command(remove, "Uninstall a pack").
pack_command(publish, "Register a pack with swi-prolog.org").
pack_command(help, "Help on command (also swipl pack command -h)").

Expand Down Expand Up @@ -162,6 +167,12 @@
pack_install:opt_meta(commit, 'HASH').
pack_install:opt_meta(server, 'URL').

pack_rebuild:opt_type(dir, pack_directory, directory).

pack_rebuild:opt_help(help(usage),
" rebuild [--dir=DIR] [pack ...]").
pack_rebuild:opt_help(pack_directory, "Rebuild packs in directory").

pack_publish:opt_type(git, git, boolean).
pack_publish:opt_type(sign, sign, boolean).
pack_publish:opt_type(force, force, boolean).
Expand Down Expand Up @@ -245,6 +256,15 @@
cli_pack_install(_, _) =>
argv_usage(pack_install:debug).

cli_pack_rebuild(Packs, Options),
select_option(pack_directory(Dir), Options, Options1) =>
attach_packs(Dir, [replace(true)]),
cli_pack_rebuild(Packs, [installed(true)|Options1]).
cli_pack_rebuild([], _Options) =>
cli(pack_rebuild).
cli_pack_rebuild(Packs, _Options) =>
cli(forall(member(Pack, Packs), pack_rebuild(Pack))).

cli_pack_remove(Packs, Options), Packs \== [] =>
cli(forall(member(Pack, Packs), pack_remove(Pack, Options))).
cli_pack_remove(_, _) =>
Expand Down

0 comments on commit 5ee1ee7

Please sign in to comment.