Skip to content

Commit 5424bab

Browse files
committed
Fixes after review
* 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.
1 parent 9000258 commit 5424bab

File tree

3 files changed

+36
-27
lines changed

3 files changed

+36
-27
lines changed

src/lib/reif.pl

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,7 @@
2424
*/
2525

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

2929
:- meta_predicate(if_(1, 0, 0)).
3030
:- meta_predicate(cond_t(1, 0, ?)).
@@ -99,8 +99,9 @@
9999

100100
%
101101
user:goal_expansion(if_(If_1, Then_0, Else_0), G_0) :-
102-
cut_contained(Then_0, SanitizedThen_0),
103-
ugoal_expansion(if_(If_1, SanitizedThen_0, Else_0), G_0).
102+
goal_sanitized(Then_0, SanitizedThen_0),
103+
goal_sanitized(Else_0, SanitizedElse_0),
104+
ugoal_expansion(if_(If_1, SanitizedThen_0, SanitizedElse_0), G_0).
104105

105106
%
106107
%

src/loader.pl

Lines changed: 20 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@
99
use_module/1,
1010
use_module/2,
1111
current_module/1,
12-
cut_contained/2
12+
goal_sanitized/2
1313
]).
1414

1515
:- use_module(library(error)).
@@ -44,7 +44,10 @@
4444
'$fail'.
4545

4646

47-
%% cut_contained(?G_0, ?S_0).
47+
never(_) :- fail.
48+
49+
50+
%% goal_sanitized(?G_0, ?S_0).
4851
%
4952
% Both `G_0` and `S_0` are valid callable terms having the same meaning, but
5053
% additionally `S_0` is safe to be called in combination with surrounding
@@ -56,13 +59,13 @@
5659
% choice points generated by `b`, but since `S_0 = call((a,!))` then
5760
% `b, call((a,!))` is safe.
5861
%
59-
% TODO: Should it be marked with meta_predicate(cut_contained(:,-))?
62+
% TODO: Should it be marked with meta_predicate(goal_sanitized(:,-))?
6063
%
61-
cut_contained(G, S) :-
62-
catch(cut_contained_aux(G, S), stop(_), false).
64+
goal_sanitized(G, S) :-
65+
catch(goal_sanitized_aux(G, S), stop(_), false).
6366

64-
cut_contained_aux(G, call(G)) :- cuts_outside(G).
65-
cut_contained_aux(G, G ) :- \+ cuts_outside(G).
67+
goal_sanitized_aux(G, call(G)) :- cuts_outside(G).
68+
goal_sanitized_aux(G, G ) :- \+ cuts_outside(G).
6669

6770

6871
%% cuts_outside(?G_0).
@@ -74,14 +77,18 @@
7477
% removes choice points generated by `a`, but fails for `a, (! -> b)` and
7578
% `a, \+ \+ !`.
7679
%
77-
cuts_outside(G) :- callable_term(G), cuts_outside_aux(G).
80+
cuts_outside(G_0) :- cuts_outside(G_0, =(!)).
81+
82+
%% cuts_outside(?G_0, +StopCondition_1).
83+
%
84+
cuts_outside(G, C_1) :- callable_term(G), cuts_outside_aux(G, C_1).
7885

79-
cuts_outside_aux(!).
80-
cuts_outside_aux(M:A) :- module_name(M), cuts_outside(A).
81-
cuts_outside_aux((A,B)) :- cuts_outside(B); cuts_outside(A).
82-
cuts_outside_aux((A;B)) :- cuts_outside(B); cuts_outside(A).
86+
cuts_outside_aux(G, C_1) :- call(C_1, G).
87+
cuts_outside_aux(M:A, C_1) :- module_name(M), cuts_outside(A, C_1).
88+
cuts_outside_aux((A,B), C_1) :- cuts_outside(B, C_1); cuts_outside(A, C_1).
89+
cuts_outside_aux((A;B), C_1) :- cuts_outside(B, C_1); cuts_outside(A, C_1).
8390
% FIXME: There is an issue with `C, (! -> B)` construct, see #2739
84-
cuts_outside_aux((_->B)) :- cuts_outside(B).
91+
cuts_outside_aux((A->B), C_1) :- cuts_outside(A, loader:never); cuts_outside(B, C_1).
8592

8693

8794
module_name(M) :-

src/tests/reif.pl

Lines changed: 12 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -127,18 +127,19 @@
127127
catch((cuts_outside(_:!),false), E3, E3 = stop(type_error(atom,_))),
128128
(G0 = a(G0), catch((cuts_outside(G0),false), E4, E4 = stop(type_error(acyclic_term,_)))),
129129
(G1 = m:G1, catch((cuts_outside(G1),false), E5, E5 = stop(type_error(acyclic_term,_)))),
130-
(cut_contained(a, X0), X0 == a),
131-
(cut_contained(!, X1), X1 == call(!)),
132-
(cut_contained((a,b;c,d), X2), X2 == (a,b;c,d)),
133-
(cut_contained((\+ \+ a), X3), X3 == (\+ \+ a)),
130+
catch((cuts_outside((6->a)),false), E6, E6 == stop(type_error(callable,6))),
131+
(goal_sanitized(a, X0), X0 == a),
132+
(goal_sanitized(!, X1), X1 == call(!)),
133+
(goal_sanitized((a,b;c,d), X2), X2 == (a,b;c,d)),
134+
(goal_sanitized((\+ \+ a), X3), X3 == (\+ \+ a)),
134135
% Questionable test case, see #2739
135-
(cut_contained((!,a->c;d), X4), X4 == (!,a->c;d)),
136-
(cut_contained((x,a->!;d), X5), X5 == call((x,a->!;d))),
137-
(cut_contained((a,b,c,!), X6), X6 == call((a,b,c,!))),
138-
\+ cut_contained(0, _),
139-
\+ cut_contained(_, _),
140-
\+ cut_contained((a,_), _),
141-
\+ cut_contained((a,b;1), _)
136+
(goal_sanitized((!,a->c;d), X4), X4 == (!,a->c;d)),
137+
(goal_sanitized((x,a->!;d), X5), X5 == call((x,a->!;d))),
138+
(goal_sanitized((a,b,c,!), X6), X6 == call((a,b,c,!))),
139+
\+ goal_sanitized(0, _),
140+
\+ goal_sanitized(_, _),
141+
\+ goal_sanitized((a,_), _),
142+
\+ goal_sanitized((a,b;1), _)
142143
]),
143144
phrase(format_("callable cut: ~q", [T]), W).
144145

0 commit comments

Comments
 (0)