Skip to content

Commit

Permalink
ENHANCED: make/0: no longer try to update the indices of system libra…
Browse files Browse the repository at this point in the history
…ries.

These libraries are properly maintained by the build and installation
process while the time stamps are often wrong after the installation
process.
  • Loading branch information
JanWielemaker committed Jun 3, 2024
1 parent 8bc1795 commit 28b3af7
Show file tree
Hide file tree
Showing 2 changed files with 24 additions and 10 deletions.
29 changes: 21 additions & 8 deletions boot/autoload.pl
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
Author: Jan Wielemaker
E-mail: J.Wielemaker@vu.nl
WWW: http://www.swi-prolog.org
Copyright (c) 1985-2023, University of Amsterdam
Copyright (c) 1985-2024, University of Amsterdam
VU University Amsterdam
CWI, Amsterdam
SWI-Prolog Solutions b.v.
Expand Down Expand Up @@ -39,7 +39,7 @@
[ '$find_library'/5,
'$in_library'/3,
'$define_predicate'/1,
'$update_library_index'/0,
'$update_library_index'/1, % +Options
'$autoload'/1,

make_library_index/1,
Expand Down Expand Up @@ -136,15 +136,20 @@
:- thread_local
silent/0.

%! '$update_library_index'
%! '$update_library_index'(+Options)
%
% Called from make/0 to update the index of the library for each
% library directory that has a writable index. Note that in the
% Windows version access_file/2 is mostly bogus. We assert
% silent/0 to suppress error messages.
% silent/0 to suppress error messages. Options:
%
% - system(+Boolean)
% Do (not) include system libraries. Default `false`.
% - user(+Boolean)
% Do (not) include user libraries. Default `true`.

'$update_library_index' :-
setof(Dir, writable_indexed_directory(Dir), Dirs),
'$update_library_index'(Options) :-
setof(Dir, writable_indexed_directory(Dir, Options), Dirs),
!,
setup_call_cleanup(
asserta(silent, Ref),
Expand All @@ -154,7 +159,7 @@
-> reload_library_index
; true
).
'$update_library_index'.
'$update_library_index'(_).

guarded_make_library_index([]).
guarded_make_library_index([Dir|Dirs]) :-
Expand All @@ -165,11 +170,19 @@
),
guarded_make_library_index(Dirs).

%! writable_indexed_directory(-Dir) is nondet.
%! writable_indexed_directory(-Dir, +Options) is nondet.
%
% True when Dir is an indexed library directory with a writable
% index, i.e., an index that can be updated.

writable_indexed_directory(Dir, Options) :-
current_prolog_flag(home, Home),
writable_indexed_directory(Dir),
( sub_atom(Dir, 0, _, _, Home)
-> '$option'(system(true), Options, false)
; '$option'(user(true), Options, true)
).

writable_indexed_directory(Dir) :-
index_file_name(IndexFile, autoload('INDEX'), [access([read,write])]),
file_directory_name(IndexFile, Dir).
Expand Down
5 changes: 3 additions & 2 deletions library/make.pl
Original file line number Diff line number Diff line change
Expand Up @@ -3,9 +3,10 @@
Author: Jan Wielemaker
E-mail: J.Wielemaker@vu.nl
WWW: http://www.swi-prolog.org
Copyright (c) 2003-2020, University of Amsterdam
Copyright (c) 2003-2024, University of Amsterdam
VU University Amsterdam
CWI, Amsterdam
SWI-Prolog Solutions b.v.
All rights reserved.
Redistribution and use in source and binary forms, with or without
Expand Down Expand Up @@ -80,7 +81,7 @@
notrace(make_no_trace).

make_no_trace :-
'$update_library_index',
'$update_library_index'([]),
findall(File, modified_file(File), Reload0),
list_to_set(Reload0, Reload),
( prolog:make_hook(before, Reload)
Expand Down

0 comments on commit 28b3af7

Please sign in to comment.