Skip to content

Commit 9000258

Browse files
committed
Skip if_/3 inlining if Then_0 is unsafe or invalid
As a part of optimization goal expansion in library(reif) inlines Then_0 argument verbatim into predicate body – this avoids unnecessary call/N invocations and dramatically increases performance, but not all goals are safe to be inlined in such a way. Here we are skipping this optimization if !s or invalid goal were detected to prevent undesired side-effects from leaking into outer goals.
1 parent e5a412c commit 9000258

File tree

3 files changed

+91
-7
lines changed

3 files changed

+91
-7
lines changed

src/lib/reif.pl

+3-6
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,7 @@
2424
*/
2525

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

2829
:- meta_predicate(if_(1, 0, 0)).
2930
:- meta_predicate(cond_t(1, 0, ?)).
@@ -91,19 +92,15 @@
9192
sameargs(0, _, _).
9293

9394

94-
/*
95-
no !s that cut outside.
96-
no variables in place of goals
97-
no malformed goals like integers
98-
*/
9995

10096

10197
/* 2do: unqualified If_1: error
10298
*/
10399

104100
%
105101
user:goal_expansion(if_(If_1, Then_0, Else_0), G_0) :-
106-
ugoal_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).
107104

108105
%
109106
%

src/loader.pl

+56-1
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,8 @@
88
strip_module/3,
99
use_module/1,
1010
use_module/2,
11-
current_module/1
11+
current_module/1,
12+
cut_contained/2
1213
]).
1314

1415
:- use_module(library(error)).
@@ -42,6 +43,60 @@
4243
nl,
4344
'$fail'.
4445

46+
47+
%% cut_contained(?G_0, ?S_0).
48+
%
49+
% Both `G_0` and `S_0` are valid callable terms having the same meaning, but
50+
% additionally `S_0` is safe to be called in combination with surrounding
51+
% goals, without worrying that cut side-effect will escape and contaminate
52+
% outer goals. `S_0 = call(G_0)` when it contains callable !s that cut outside,
53+
% and `S_0 = G_0` otherwise.
54+
%
55+
% For example: given `G_0 = (a,!)` then compound goal `b,a,!` will remove
56+
% choice points generated by `b`, but since `S_0 = call((a,!))` then
57+
% `b, call((a,!))` is safe.
58+
%
59+
% TODO: Should it be marked with meta_predicate(cut_contained(:,-))?
60+
%
61+
cut_contained(G, S) :-
62+
catch(cut_contained_aux(G, S), stop(_), false).
63+
64+
cut_contained_aux(G, call(G)) :- cuts_outside(G).
65+
cut_contained_aux(G, G ) :- \+ cuts_outside(G).
66+
67+
68+
%% cuts_outside(?G_0).
69+
%
70+
% `G_0` is a goal for which side-effects of a cut may spill out to the
71+
% surrounding goals. Throws `stop(_)` when it doesn't represent a valid goal.
72+
%
73+
% For example it succeeds for terms `a, (!, b)` and `a, b -> !` where cut
74+
% removes choice points generated by `a`, but fails for `a, (! -> b)` and
75+
% `a, \+ \+ !`.
76+
%
77+
cuts_outside(G) :- callable_term(G), cuts_outside_aux(G).
78+
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).
83+
% FIXME: There is an issue with `C, (! -> B)` construct, see #2739
84+
cuts_outside_aux((_->B)) :- cuts_outside(B).
85+
86+
87+
module_name(M) :-
88+
atom(M) -> true; throw(stop(type_error(atom,M))).
89+
90+
91+
callable_term(T) :-
92+
callable(T) ->
93+
( acyclic_term(T) ->
94+
true
95+
; throw(stop(type_error(acyclic_term,T)))
96+
)
97+
; throw(stop(type_error(callable,T))).
98+
99+
45100
expand_term(Term, ExpandedTerm) :-
46101
( '$predicate_defined'(user, term_expansion, 2),
47102
catch(user:term_expansion(Term, ExpandedTerm0),

src/tests/reif.pl

+32
Original file line numberDiff line numberDiff line change
@@ -110,6 +110,38 @@
110110
Solutions == [if_(1=1,a=a,2), error(type_error(callable,2),call/1)]
111111
)).
112112

113+
test(W, loader:call(T)) :-
114+
member(T, [
115+
cuts_outside(!),
116+
cuts_outside(foo:!),
117+
cuts_outside((a,!)),
118+
cuts_outside((!;b(_))),
119+
cuts_outside(((a;b(_,_);c),!,d)),
120+
\+ cuts_outside(call((a,!))),
121+
\+ cuts_outside(((a;b;c),\+ !,d)),
122+
\+ cuts_outside((! -> a; b)),
123+
\+ cuts_outside(((x,!;y) -> a; b)),
124+
catch((cuts_outside(_),false), E0, E0 = stop(type_error(callable,_))),
125+
catch((cuts_outside(2),false), E1, E1 == stop(type_error(callable,2))),
126+
catch((cuts_outside(1:!),false), E2, E2 == stop(type_error(atom,1))),
127+
catch((cuts_outside(_:!),false), E3, E3 = stop(type_error(atom,_))),
128+
(G0 = a(G0), catch((cuts_outside(G0),false), E4, E4 = stop(type_error(acyclic_term,_)))),
129+
(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)),
134+
% 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), _)
142+
]),
143+
phrase(format_("callable cut: ~q", [T]), W).
144+
113145
result_or_exception(Goal, Result) :-
114146
catch((Goal,Result=Goal), Result, true).
115147

0 commit comments

Comments
 (0)