apply_macros.pl -- Goal expansion rules to avoid meta-calling
This module defines goal_expansion/2 rules to deal with commonly used, but fundamentally slow meta-predicates. Notable maplist/2... defines a useful set of predicates, but its execution is considerable slower than a traditional Prolog loop. Using this library calls to maplist/2... are translated into an call to a generated auxiliary predicate that is compiled using compile_aux_clauses/1. Currently this module supports:
The idea for this library originates from ECLiPSe and came to SWI-Prolog through YAP.
- expand_maplist(+Callable, +Lists, -Goal) is det[private]
- Macro expansion for maplist/2 and higher arity. The first clause deals with code using maplist on fixed lists to reduce typing. Note that we only expand if all lists have fixed length. In theory we only need at least one of fixed length, but in that case the goal expansion instantiates variables in the clause, causing issues with the remainder of the clause expansion mechanism.
- maplist_extend_goal(+Closure, +Args, -Goal) is semidet[private]
- Extend the maplist Closure with Args. This can be tricky. Notably library(yall) lambda expressions may instantiate the Closure while the real execution does not. We can solve that by using lambda_calls/3. The expand_goal_no_instantiate/2 ensures safe goal expansion.
- expand_closure_no_fail(+Goal, +Extra:integer, -GoalExt) is det[private]
- Add Extra additional arguments to Goal.
- expand_apply(+GoalIn:callable, -GoalOut) is semidet[private]
- Macro expansion for `apply' predicates.
- expand_apply(+GoalIn:callable, -GoalOut, +PosIn, -PosOut) is semidet[private]
- Translation of simple meta calls to inline code while
maintaining position information. Note that
once(Goal)
cannot be translated to(Goal->true)
because this will break the compilation of(once(X) ; Y)
. A correct translation is to(Goal->true;fail)
. Abramo Bagnara suggested((Goal->true),true)
, which is both faster and avoids warning ifstyle_check(+var_branches)
is used. - expand_phrase(+PhraseGoal, -Goal) is semidet
- expand_phrase(+PhraseGoal, +Pos0, -Goal, -Pos) is semidet
- Provide goal-expansion for PhraseGoal. PhraseGoal is either
phrase/2,3 or call_dcg/2,3. The current version does not
translate control structures, but only simple terminals and
non-terminals.
For example:
?- expand_phrase(phrase(("ab", rule)), List), Goal). Goal = (List=[97, 98|_G121], rule(_G121, [])).
- dcg_extend(+Callable, +Pos0, -Goal, -Pos, +Xs0, ?Xs) is semidet[private]
- qcall_instantiated(@Term) is semidet[private]
- True if Term is instantiated sufficiently to call it.
- apply_macros_sentinel
- Used to detect that library(apply_macros) is loaded into the current
context explicitly. This test is used if the Prolog flag
apply_macros
is set toimported
.
Re-exported predicates
The following predicates are exported from this file while their implementation is defined in imported modules or non-module files loaded by this module.
- expand_phrase(+PhraseGoal, -Goal) is semidet
- expand_phrase(+PhraseGoal, +Pos0, -Goal, -Pos) is semidet
- Provide goal-expansion for PhraseGoal. PhraseGoal is either
phrase/2,3 or call_dcg/2,3. The current version does not
translate control structures, but only simple terminals and
non-terminals.
For example:
?- expand_phrase(phrase(("ab", rule)), List), Goal). Goal = (List=[97, 98|_G121], rule(_G121, [])).