Skip to content

Commit

Permalink
FIXED: Preserve table properties on reconsult.
Browse files Browse the repository at this point in the history
Reported by Jan Burse.
  • Loading branch information
JanWielemaker committed Oct 8, 2023
1 parent 4e6420e commit 9e1303a
Show file tree
Hide file tree
Showing 3 changed files with 23 additions and 3 deletions.
14 changes: 14 additions & 0 deletions src/Tests/unprotected/reload/keep_tabling.pl
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
:- table p/2.

p(A,A).
p(A,C) :- p(A,B), e(B, C).
e(a,b).
e(b,c).
%%%%%%%%%%%%%%%%
:- table p/2.

p(A,A).
p(A,C) :- p(A,B), e(B, C).
e(a,b).
e(b,c).

8 changes: 7 additions & 1 deletion src/Tests/unprotected/test_reload.pl
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,9 @@
Author: Jan Wielemaker
E-mail: [email protected]
WWW: http://www.swi-prolog.org
Copyright (c) 2015-2016, University of Amsterdam
Copyright (c) 2015-2023, University of Amsterdam
VU University Amsterdam
SWI-Prolog Solutions b.v.
All rights reserved.
Redistribution and use in source and binary forms, with or without
Expand Down Expand Up @@ -177,6 +178,11 @@
test(goal_expansion) :-
reload(goal_expansion, 1),
reload(goal_expansion, 1).
test(keep_tabling, [Name1, Wrapped1, Body1] =@= [Name2, Wrapped2, Body2]) :-
reload(keep_tabling, 1),
current_predicate_wrapper(keep_tabling:p(_,_), Name1, Wrapped1, Body1),
reload(keep_tabling, 2),
current_predicate_wrapper(keep_tabling:p(_,_), Name2, Wrapped2, Body2).

:- end_tests(reconsult).

Expand Down
4 changes: 2 additions & 2 deletions src/pl-srcfile.c
Original file line number Diff line number Diff line change
Expand Up @@ -1368,11 +1368,11 @@ fix_metapredicate(p_reload *r)
clear(def, P_TRANSPARENT);
set(def, r->flags&P_TRANSPARENT);

freeCodesDefinition(def, FALSE);
freeCodesDefinition(def, TRUE);
}
} else if ( true(r, P_META) )
{ setMetapredicateMask(def, r->args);
freeCodesDefinition(def, FALSE);
freeCodesDefinition(def, TRUE);
} else if ( true(r, P_TRANSPARENT) )
{ set(def, P_TRANSPARENT);
}
Expand Down

0 comments on commit 9e1303a

Please sign in to comment.