Skip to content

Commit

Permalink
ENHANCED: pack_info/1: use colours and indicate autoload status.
Browse files Browse the repository at this point in the history
  • Loading branch information
JanWielemaker committed Dec 4, 2024
1 parent c6256bd commit 6f2e587
Showing 1 changed file with 10 additions and 4 deletions.
14 changes: 10 additions & 4 deletions library/prolog_pack.pl
Original file line number Diff line number Diff line change
Expand Up @@ -201,12 +201,13 @@
multi_valued(T, LabelFmt, LT, MoreValues).


pvalue_column(29).
pvalue_column(31).
print_property_value(Prop-Fmt, Values) :-
!,
pvalue_column(C),
atomic_list_concat(['~w:~t~*|', Fmt, '~n'], Format),
format(Format, [Prop,C|Values]).
ansi_format(comment, '% ~w:~t~*|', [Prop, C]),
ansi_format(code, Fmt, Values),
ansi_format([], '~n', []).

pack_info(Name, Level, Info) :-
'$pack':pack(Name, BaseDir),
Expand Down Expand Up @@ -236,6 +237,7 @@
pack_level_info(_, conflicts(_), 'Conflicts with', -).
pack_level_info(_, replaces(_), 'Replaces packages', -).
pack_level_info(info, library(_), 'Provided libraries', -).
pack_level_info(info, autoload(_), 'Autoload', -).

pack_default(Level, Infos, Def) :-
pack_level_info(Level, ITerm, _Format, Def),
Expand All @@ -260,7 +262,11 @@
expand_file_name(Pattern, Files),
maplist(atom_concat(LibDir), Plain, Files),
convlist(base_name, Plain, Libs),
member(Lib, Libs).
member(Lib, Libs),
Lib \== 'INDEX'.
pack_info_term(BaseDir, autoload(true)) :-
atom_concat(BaseDir, '/prolog/INDEX.pl', IndexFile),
exists_file(IndexFile).
pack_info_term(BaseDir, automatic(Boolean)) :-
once(pack_status_dir(BaseDir, automatic(Boolean))).
pack_info_term(BaseDir, built(Arch, Prolog)) :-
Expand Down

0 comments on commit 6f2e587

Please sign in to comment.