Skip to content

Commit

Permalink
Fixes after review
Browse files Browse the repository at this point in the history
  * Rename predicate cut_contained to goal_sanitized
  * Apply wrapping to both Then_0 and Else_0 branches of if_/3
  * Apply cut and invalid goal detection to left argument of (_ -> B) term.
  • Loading branch information
hurufu committed Jan 5, 2025
1 parent 9000258 commit 5424bab
Show file tree
Hide file tree
Showing 3 changed files with 36 additions and 27 deletions.
7 changes: 4 additions & 3 deletions src/lib/reif.pl
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,7 @@
*/

:- use_module(library(dif)).
:- use_module(library(loader), [cut_contained/2]).
:- use_module(library(loader), [goal_sanitized/2]).

:- meta_predicate(if_(1, 0, 0)).
:- meta_predicate(cond_t(1, 0, ?)).
Expand Down Expand Up @@ -99,8 +99,9 @@

%
user:goal_expansion(if_(If_1, Then_0, Else_0), G_0) :-
cut_contained(Then_0, SanitizedThen_0),
ugoal_expansion(if_(If_1, SanitizedThen_0, Else_0), G_0).
goal_sanitized(Then_0, SanitizedThen_0),
goal_sanitized(Else_0, SanitizedElse_0),
ugoal_expansion(if_(If_1, SanitizedThen_0, SanitizedElse_0), G_0).

%
%
Expand Down
33 changes: 20 additions & 13 deletions src/loader.pl
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@
use_module/1,
use_module/2,
current_module/1,
cut_contained/2
goal_sanitized/2
]).

:- use_module(library(error)).
Expand Down Expand Up @@ -44,7 +44,10 @@
'$fail'.


%% cut_contained(?G_0, ?S_0).
never(_) :- fail.


%% goal_sanitized(?G_0, ?S_0).
%
% Both `G_0` and `S_0` are valid callable terms having the same meaning, but
% additionally `S_0` is safe to be called in combination with surrounding
Expand All @@ -56,13 +59,13 @@
% choice points generated by `b`, but since `S_0 = call((a,!))` then
% `b, call((a,!))` is safe.
%
% TODO: Should it be marked with meta_predicate(cut_contained(:,-))?
% TODO: Should it be marked with meta_predicate(goal_sanitized(:,-))?
%
cut_contained(G, S) :-
catch(cut_contained_aux(G, S), stop(_), false).
goal_sanitized(G, S) :-
catch(goal_sanitized_aux(G, S), stop(_), false).

cut_contained_aux(G, call(G)) :- cuts_outside(G).
cut_contained_aux(G, G ) :- \+ cuts_outside(G).
goal_sanitized_aux(G, call(G)) :- cuts_outside(G).
goal_sanitized_aux(G, G ) :- \+ cuts_outside(G).


%% cuts_outside(?G_0).
Expand All @@ -74,14 +77,18 @@
% removes choice points generated by `a`, but fails for `a, (! -> b)` and
% `a, \+ \+ !`.
%
cuts_outside(G) :- callable_term(G), cuts_outside_aux(G).
cuts_outside(G_0) :- cuts_outside(G_0, =(!)).

%% cuts_outside(?G_0, +StopCondition_1).
%
cuts_outside(G, C_1) :- callable_term(G), cuts_outside_aux(G, C_1).

cuts_outside_aux(!).
cuts_outside_aux(M:A) :- module_name(M), cuts_outside(A).
cuts_outside_aux((A,B)) :- cuts_outside(B); cuts_outside(A).
cuts_outside_aux((A;B)) :- cuts_outside(B); cuts_outside(A).
cuts_outside_aux(G, C_1) :- call(C_1, G).
cuts_outside_aux(M:A, C_1) :- module_name(M), cuts_outside(A, C_1).
cuts_outside_aux((A,B), C_1) :- cuts_outside(B, C_1); cuts_outside(A, C_1).
cuts_outside_aux((A;B), C_1) :- cuts_outside(B, C_1); cuts_outside(A, C_1).
% FIXME: There is an issue with `C, (! -> B)` construct, see #2739
cuts_outside_aux((_->B)) :- cuts_outside(B).
cuts_outside_aux((A->B), C_1) :- cuts_outside(A, loader:never); cuts_outside(B, C_1).


module_name(M) :-
Expand Down
23 changes: 12 additions & 11 deletions src/tests/reif.pl
Original file line number Diff line number Diff line change
Expand Up @@ -127,18 +127,19 @@
catch((cuts_outside(_:!),false), E3, E3 = stop(type_error(atom,_))),
(G0 = a(G0), catch((cuts_outside(G0),false), E4, E4 = stop(type_error(acyclic_term,_)))),
(G1 = m:G1, catch((cuts_outside(G1),false), E5, E5 = stop(type_error(acyclic_term,_)))),
(cut_contained(a, X0), X0 == a),
(cut_contained(!, X1), X1 == call(!)),
(cut_contained((a,b;c,d), X2), X2 == (a,b;c,d)),
(cut_contained((\+ \+ a), X3), X3 == (\+ \+ a)),
catch((cuts_outside((6->a)),false), E6, E6 == stop(type_error(callable,6))),
(goal_sanitized(a, X0), X0 == a),
(goal_sanitized(!, X1), X1 == call(!)),
(goal_sanitized((a,b;c,d), X2), X2 == (a,b;c,d)),
(goal_sanitized((\+ \+ a), X3), X3 == (\+ \+ a)),
% Questionable test case, see #2739
(cut_contained((!,a->c;d), X4), X4 == (!,a->c;d)),
(cut_contained((x,a->!;d), X5), X5 == call((x,a->!;d))),
(cut_contained((a,b,c,!), X6), X6 == call((a,b,c,!))),
\+ cut_contained(0, _),
\+ cut_contained(_, _),
\+ cut_contained((a,_), _),
\+ cut_contained((a,b;1), _)
(goal_sanitized((!,a->c;d), X4), X4 == (!,a->c;d)),
(goal_sanitized((x,a->!;d), X5), X5 == call((x,a->!;d))),
(goal_sanitized((a,b,c,!), X6), X6 == call((a,b,c,!))),
\+ goal_sanitized(0, _),
\+ goal_sanitized(_, _),
\+ goal_sanitized((a,_), _),
\+ goal_sanitized((a,b;1), _)
]),
phrase(format_("callable cut: ~q", [T]), W).

Expand Down

0 comments on commit 5424bab

Please sign in to comment.