Skip to content

Commit

Permalink
Keep track of pack providing directories by updating file_search_path/2.
Browse files Browse the repository at this point in the history
  • Loading branch information
JanWielemaker committed Jan 12, 2024
1 parent 70b3191 commit 47c034b
Showing 1 changed file with 6 additions and 12 deletions.
18 changes: 6 additions & 12 deletions boot/packs.pl
Original file line number Diff line number Diff line change
Expand Up @@ -40,16 +40,14 @@
attach_packs/2, % +Dir, +Options
'$pack_detach'/2, % +Name, -Dir
'$pack_attach'/1, % +Dir
'$pack_attach'/2, % +Dir, +Options
'$packs_from'/1 % ?Dir
'$pack_attach'/2 % +Dir, +Options
]).

:- multifile user:file_search_path/2.
:- dynamic user:file_search_path/2.

:- dynamic
pack_dir/3, % Pack, Type, Dir
packs_from/1, % Dir
pack/2. % Pack, BaseDir

user:file_search_path(pack, app_data(pack)).
Expand Down Expand Up @@ -93,9 +91,6 @@
; '$domain_error'(pack, Dir)
).

'$packs_from'(Dir) :-
packs_from(Dir).

%! attach_packs
%
% Attach packages from all package directories. If there are
Expand Down Expand Up @@ -174,7 +169,7 @@
( '$option'(replace(true), Options)
-> forall(pack(Name, PackDir),
'$pack_detach'(Name, PackDir)),
retractall(packs_from(_))
retractall(user:file_search_path(pack, _))
; true
),
register_packs_from(Dir),
Expand All @@ -190,11 +185,10 @@
attach_packs(_, _).

register_packs_from(Dir) :-
packs_from(Dir),
!.
register_packs_from(Dir) :-
asserta(packs_from(Dir)),
!.
( user:file_search_path(pack, Dir)
-> true
; asserta(user:file_search_path(pack, Dir))
).

attach_packages([], _, _).
attach_packages([H|T], Dir, Options) :-
Expand Down

0 comments on commit 47c034b

Please sign in to comment.