Skip to content

Commit

Permalink
FIXED: Handling of the Prolog flag compile_meta_arguments.
Browse files Browse the repository at this point in the history
  • Loading branch information
JanWielemaker committed Nov 25, 2020
1 parent 9163d3c commit f64d3f0
Show file tree
Hide file tree
Showing 2 changed files with 49 additions and 20 deletions.
34 changes: 32 additions & 2 deletions boot/expand.pl
Expand Up @@ -1421,10 +1421,12 @@
sub_atom(Name, 0, _, _, '__aux_meta_call_').

compile_meta(CallIn, CallOut, M, Term, (CallOut :- Body)) :-
term_variables(Term, AllVars),
replace_subterm(CallIn, true, Term, Term2),
term_variables(Term2, AllVars),
term_variables(CallIn, InVars),
intersection_eq(InVars, AllVars, HeadVars),
variant_sha1(CallIn+HeadVars, Hash),
copy_term_nat(CallIn+HeadVars, NAT),
variant_sha1(NAT, Hash),
atom_concat('__aux_meta_call_', Hash, AuxName),
expand_goal(CallIn, _Pos0, Body, _Pos, M, [], (CallOut:-CallIn), []),
length(HeadVars, Arity),
Expand All @@ -1434,6 +1436,34 @@
),
CallOut =.. [AuxName|HeadArgs].

%! replace_subterm(From, To, TermIn, TermOut)
%
% Replace instances (==/2) of From inside TermIn by To.

replace_subterm(From, To, TermIn, TermOut) :-
From == TermIn,
!,
TermOut = To.
replace_subterm(From, To, TermIn, TermOut) :-
compound(TermIn),
compound_name_arity(TermIn, Name, Arity),
Arity > 0,
!,
compound_name_arity(TermOut, Name, Arity),
replace_subterm_compound(1, Arity, From, To, TermIn, TermOut).
replace_subterm(_, _, Term, Term).

replace_subterm_compound(I, Arity, From, To, TermIn, TermOut) :-
I =< Arity,
!,
arg(I, TermIn, A1),
arg(I, TermOut, A2),
replace_subterm(From, To, A1, A2),
I2 is I+1,
replace_subterm_compound(I2, Arity, From, To, TermIn, TermOut).
replace_subterm_compound(_I, _Arity, _From, _To, _TermIn, _TermOut).


%! intersection_eq(+Small, +Big, -Shared) is det.
%
% Shared are the variables in Small that also appear in Big. The
Expand Down
35 changes: 17 additions & 18 deletions man/overview.doc
Expand Up @@ -1265,29 +1265,28 @@ print_message/2.
\end{itemize}

\prologflagitem{compile_meta_arguments}{atom}{rw}
Experimental flag that controls compilation of arguments passed to
meta-calls marked `0' or `\chr{^}' (see meta_predicate/1). Supported
values are:
This flag controls compilation of arguments passed to meta-calls marked
`0' or `\chr{^}' (see meta_predicate/1). Supported values are:

\begin{description}
\termitem{false}{}
(default). Meta-arguments are passed verbatim.
(default). Meta-arguments are passed verbatim. If the argument is a
control structure ((A,B), (A;B), (A->B;C), etc.) it is compile to an
temporary clause allocated on the environment stack when the
meta-predicate is called.

\termitem{control}{}
Compile meta-arguments that contain control structures ((A,B), (A;B),
(A->B;C), etc.). If not compiled at compile time, such arguments are
compiled to a temporary clause before execution. Using this option
enhances performance of processing complex meta-goals that are known
at compile time.
\termitem{true}{}
Also compile references to normal user predicates. This harms
performance (a little), but enhances the power of poor-mens consistency
check used by make/0 and implemented by list_undefined/0.
Compile meta-arguments that contain control structures to an auxiliary
predicate. This generally improves performance as well as the debugging
experience.

\termitem{always}{}
Always create an intermediate clause, even for system predicates. This
prepares for replacing the normal head of the generated predicate with
a special reference (similar to database references as used by, e.g.,
assert/2) that provides direct access to the executable code, thus
avoiding runtime lookup of predicates for meta-calling.
Always create an intermediate clause, even for system
predicates.\footnote{This may be used in the future for
replacing the normal head of the generated predicate with a special
reference (similar to database references as used by, e.g., assert/2)
that provides direct access to the executable code, thus avoiding
runtime lookup of predicates for meta-calling.}
\end{description}

\prologflagitem{compiled_at}{atom}{r}
Expand Down

0 comments on commit f64d3f0

Please sign in to comment.