Skip to content

Commit

Permalink
FIXED: Handle source files with epoch time stamp
Browse files Browse the repository at this point in the history
Flatpak seems to set the modification time of all times in the sandbox
to the epoch (0).  This was used as a special value to indicate the
source file was not a file.   We now keep a seperate flag and use the
_integer_ 0 to indicate something is not a source file in the Prolog
world.   It is probably better to use something else, but this avoids
type issues in possibly unknown dependent code.
  • Loading branch information
JanWielemaker committed May 15, 2024
1 parent be3ff0b commit dd7f4bd
Show file tree
Hide file tree
Showing 5 changed files with 54 additions and 22 deletions.
4 changes: 2 additions & 2 deletions boot/init.pl
Original file line number Diff line number Diff line change
Expand Up @@ -2290,7 +2290,7 @@
fail.
'$noload'(_, FullFile, _Options) :-
'$time_source_file'(FullFile, Time, system),
Time > 0.0,
float(Time),
!.
'$noload'(not_loaded, FullFile, _) :-
source_file(FullFile),
Expand Down Expand Up @@ -3000,7 +3000,7 @@
error(_, _),
fail),
!.
'$modified_id'(_, 0.0, _).
'$modified_id'(_, 0, _).


'$compile_type'(What) :-
Expand Down
6 changes: 3 additions & 3 deletions boot/syspred.pl
Original file line number Diff line number Diff line change
Expand Up @@ -245,8 +245,8 @@
% if the canonical name as defined by absolute_file_name/2 is
% known as a loaded filename.
%
% Note that Time = 0.0 is used by PlDoc and other code that needs
% to create a file record without being interested in the time.
% Note that Time = 0 is used by PlDoc and other code that needs to
% create a file record without being interested in the time.

source_file(File) :-
( current_prolog_flag(access_level, user)
Expand All @@ -260,7 +260,7 @@
), !
; '$time_source_file'(File, Time, Level)
),
Time > 0.0.
float(Time).

%! source_file(+Head, -File) is semidet.
%! source_file(?Head, ?File) is nondet.
Expand Down
1 change: 1 addition & 0 deletions src/pl-incl.h
Original file line number Diff line number Diff line change
Expand Up @@ -1989,6 +1989,7 @@ struct sourceFile
unsigned int number_of_clauses; /* number of clauses */
unsigned int index; /* index number (1,2,...) */
unsigned int references; /* Reference count */
unsigned isfile : 1; /* Is a real file */
unsigned system : 1; /* system sourcefile: do not reload */
unsigned from_state : 1; /* Loaded from resource DB state */
unsigned resource : 1; /* Loaded from resource DB file */
Expand Down
29 changes: 20 additions & 9 deletions src/pl-qlf.c
Original file line number Diff line number Diff line change
Expand Up @@ -164,16 +164,16 @@ Below is an informal description of the format of a `.qlf' file:
XR_FUNCTOR <XR/name> <num> % functor
XR_PRED <XR/fdef> <XR/module>% predicate
XR_MODULE <XR/name> % module
XR_FILE 's'|'u' <XR/atom> <time>
XR_FILE 's'|'u'|'S'|'U' <XR/atom> <time>
'-'
XR_BLOB_TYPE <len><chars> % blob type-name
<term> ::= <num> % # variables in term
<theterm>
<theterm> ::= <XR/atomic> % atomic data
| 'v' <num> % variable
| 't' <XR/functor> {<theterm>} % compound
<system> ::= 's' % system source file
| 'u' % user source file
<system> ::= 's' | 'S' % system source file
| 'u' | 'U' % user source file
<time> ::= <word> % time file was loaded
<line> ::= <num>
<codes> ::= <num> {<code>}
Expand Down Expand Up @@ -841,6 +841,8 @@ loadXRc(DECL_LD wic_state *state, int c)
switch( (c=Qgetc(fd)) )
{ case 'u':
case 's':
case 'U':
case 'S':
{ atom_t name = word2atom(loadXR(state));
double time = qlfGetDouble(fd);
PL_chars_t text;
Expand All @@ -853,8 +855,9 @@ loadXRc(DECL_LD wic_state *state, int c)
PL_STRINGS_RELEASE();

if ( sf->mtime == 0.0 )
{ sf->mtime = time;
sf->system = (c == 's' ? TRUE : FALSE);
{ sf->mtime = time;
sf->system = !!(c == 's' || c == 'S');
sf->isfile = !!(c == 's' || c == 'u');
}
sf->count++;
xr = ptr2word(sf);
Expand Down Expand Up @@ -1814,7 +1817,7 @@ qlfLoadSource(wic_state *state)
{ IOSTREAM *fd = state->wicFd;
char *str = qlfGetString(fd, NULL);
double time = qlfGetDouble(fd);
unsigned int issys = (Qgetc(fd) == 's') ? TRUE : FALSE;
int ftype = Qgetc(fd);
atom_t fname;

if ( !str )
Expand All @@ -1830,7 +1833,8 @@ qlfLoadSource(wic_state *state)
state->currentSource = lookupSourceFile(fname, TRUE);
PL_unregister_atom(fname); /* locked with sourceFile */
state->currentSource->mtime = time;
state->currentSource->system = issys&0x1;
state->currentSource->system = !!(ftype == 's' || ftype == 'S');
state->currentSource->isfile = !!(ftype == 's' || ftype == 'u');
if ( GD->bootsession ) /* (**) */
state->currentSource->count++;
else
Expand Down Expand Up @@ -2485,6 +2489,13 @@ saveXRProc(DECL_LD wic_state *state, Procedure p)
saveXRModule(state, p->definition->module);
}

static inline int
src_file_status(const SourceFile f)
{ if ( f->isfile )
return f->system ? 's' : 'u';
else
return f->system ? 'S' : 'U';
}

#define saveXRSourceFile(state, f) LDFUNC(saveXRSourceFile, state, f)
static void
Expand All @@ -2499,7 +2510,7 @@ saveXRSourceFile(DECL_LD wic_state *state, SourceFile f)
if ( f )
{ DEBUG(MSG_QLF_XR, Sdprintf("XR(%d) = file %s\n",
state->savedXRTableId, stringAtom(f->name)));
Sputc(f->system ? 's' : 'u', fd);
Sputc(src_file_status(f), fd);
saveXR(state, f->name);
qlfPutDouble(f->mtime, fd);
} else
Expand Down Expand Up @@ -3666,7 +3677,7 @@ qlfSaveSource(wic_state *state, SourceFile f)
Sputc('F', fd);
qlfPutString(text.text.t, text.length, fd);
qlfPutDouble(f->mtime, fd);
Sputc(f->system ? 's' : 'u', fd);
Sputc(src_file_status(f), fd);
PL_STRINGS_RELEASE();

state->currentSource = f;
Expand Down
36 changes: 28 additions & 8 deletions src/pl-srcfile.c
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) 2014-2021, VU University Amsterdam
Copyright (c) 2014-2024, VU University Amsterdam
CWI, Amsterdam
SWI-Prolog Solutions b.v.
All rights reserved.
Expand Down Expand Up @@ -303,6 +303,7 @@ lookupSourceFile_unlocked(atom_t name, int create)
{ file = allocHeapOrHalt(sizeof(*file));
memset(file, 0, sizeof(*file));

file->mtime = 0.0;
file->name = name;
file->system = GD->bootsession&1;
file->from_state = GD->bootsession&1;
Expand Down Expand Up @@ -639,6 +640,16 @@ PRED_IMPL("$source_file_predicates", 2, source_file_predicates, 0)
}


#define unify_src_file_time(t, f) LDFUNC(unify_src_file_time, t, f)

static int
unify_src_file_time(DECL_LD term_t t, const SourceFile f)
{ if ( f->isfile )
return PL_unify_float(t, f->mtime);

return PL_unify_integer(t, 0);
}

static
PRED_IMPL("$time_source_file", 3, time_source_file, PL_FA_NONDETERMINISTIC)
{ PRED_LD
Expand Down Expand Up @@ -669,7 +680,7 @@ PRED_IMPL("$time_source_file", 3, time_source_file, PL_FA_NONDETERMINISTIC)
continue;

if ( PL_unify_atom(file, f->name) &&
PL_unify_float(time, f->mtime) &&
unify_src_file_time(time, f) &&
PL_unify_atom(type, f->system ? ATOM_system : ATOM_user) )
{ PL_close_foreign_frame(fid);
ForeignRedoInt(index+1);
Expand Down Expand Up @@ -1694,16 +1705,25 @@ static
PRED_IMPL("$start_consult", 2, start_consult, 0)
{ PRED_LD
atom_t name;
double time;

term_t file = A1;
term_t modified = A2;

if ( PL_get_atom_ex(file, &name) &&
PL_get_float_ex(modified, &time) )
{ SourceFile sf = lookupSourceFile(name, TRUE);
if ( PL_get_atom_ex(file, &name) )
{ int isfile, i;
double mtime;

if ( PL_get_integer(modified, &i) && i == 0 )
{ isfile = FALSE;
mtime = 0.0;
} else if ( PL_get_float_ex(modified, &mtime) )
{ isfile = TRUE;
} else
return FALSE;

SourceFile sf = lookupSourceFile(name, TRUE);

sf->mtime = time;
sf->mtime = mtime;
sf->isfile = isfile&1;
startConsult(sf);
releaseSourceFile(sf);

Expand Down

0 comments on commit dd7f4bd

Please sign in to comment.