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_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, [])).
- 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, [])).