Skip to content

Commit

Permalink
FIXED: pack_publish/2 reporting (claimed failure)
Browse files Browse the repository at this point in the history
  • Loading branch information
JanWielemaker committed Sep 24, 2024
1 parent 57a0635 commit 0088420
Showing 1 changed file with 28 additions and 3 deletions.
31 changes: 28 additions & 3 deletions library/prolog_pack.pl
Original file line number Diff line number Diff line change
Expand Up @@ -2883,11 +2883,21 @@
%! publish_download(+Infos, +Options) is semidet.
%! register_downloads(+Infos, +Options) is det.
%
% Register our downloads with the pack server.
% Register our downloads with the pack server. The publish_download/2
% version is used to register a specific pack after successfully
% installing the pack. In this scenario, we
%
% 1. call register_downloads/2 with publish(Pack) that must be
% a no-op.
% 2. build and test the pack
% 3. call publish_download/2, which calls register_downloads/2
% after replacing publish(Pack) by do_publish(Pack).

register_downloads(_, Options) :-
option(register(false), Options),
\+ option(do_publish(_), Options),
!.
register_downloads(_, Options) :-
option(publish(_), Options),
!.
register_downloads(Infos, Options) :-
convlist(download_data, Infos, Data),
Expand All @@ -2902,7 +2912,7 @@
( Reply = true(Actions),
memberchk(Pack-Result, Actions)
-> ( registered(Result)
-> true
-> print_message(informational, pack(published(Info, Result)))
; print_message(error, pack(publish_failed(Info, Result))),
fail
)
Expand Down Expand Up @@ -3566,6 +3576,10 @@
' differs from this tag at the origin'
].

message(published(Info, At)) -->
[ 'Published pack ' ], msg_pack(Info), msg_info_version(Info),
[' to be installed from '],
msg_published_address(At).
message(publish_failed(Info, Reason)) -->
[ 'Pack ' ], msg_pack(Info), [ ' at version ~w'-[Info.version] ],
msg_publish_failed(Reason).
Expand All @@ -3578,6 +3592,11 @@
msg_publish_failed(Status) -->
[ ' failed for unknown reason (~p)'-[Status] ].

msg_published_address(git(URL)) -->
msg_url(URL, _).
msg_published_address(file(URL)) -->
msg_url(URL, _).

candidate_dirs([]) --> [].
candidate_dirs([H|T]) --> [ nl, ' ~w'-[H] ], candidate_dirs(T).
% Questions
Expand Down Expand Up @@ -3726,6 +3745,12 @@
msg_pack(Info) -->
msg_pack(Info.pack).

msg_info_version(Info) -->
[ ansi(code, '@~w', [Info.get(version)]) ],
!.
msg_info_version(_Info) -->
[].

%! msg_build_plan(+Plan)//
%
% Describe the build plan before running the build steps.
Expand Down

0 comments on commit 0088420

Please sign in to comment.