:- use_module(library(edcg)).
% Declare accumulators
edcg:acc_info(adder, X, In, Out, plus(X,In,Out)).
% Declare predicates using these hidden arguments
edcg:pred_info(len,0,[adder,dcg]).
edcg:pred_info(increment,0,[adder]).
increment -->>
[1]:adder. % add one to the accumulator
len(Xs,N) :-
len(0,N,Xs,[]).
len -->>
[_], % 'dcg' accumulator has an element
!,
increment, % increment the 'adder' accumulator
len.
len -->>
[].
If you're using SWI-Prolog 8.3.21 or
later, you can use ==>>
, which generates clauses with =>
instead
of :-
. More details are given later in this document.
This enhancement is experimental and subject to change.
DCG notation gives us a single, hidden accumulator. Extended DCG notation (implemented by this library) lets predicates have arbitrarily many hidden accumulators. As demonstrated by the Synopsis above, those accumulators can be implemented with arbitrary goals (like plus/3).
Benefits of this library:
- avoid tedium and errors from manually threading accumulators through your predicates
- add or remove accumulators with a single declaration
- change accumulator implementation with a single declaration (ex, switching from ordsets to rbtrees)
Extended DCG syntax is very similar to DCG notation. An EDCG is created with clauses whose neck is the -->>
operator. The following syntax is supported inside an EDCG clause:
{Goal}
- don't expand any hidden arguments ofGoal
Goal
- expand all hidden arguments of Goal that are also in the head. Those hidden arguments not in the head are given default values.Goal:L
- IfGoal
has no hidden arguments then force the expansion of all arguments inL
in the order given. IfGoal
has hidden arguments then expand all of them, using the contents ofL
to override the expansion.L
is either a term of the formAcc
,Acc(Left,Right)
,Pass
,Pass(Value)
, or a list of such terms. When present, the argumentsLeft
,Right
, andValue
override the default values of arguments not in the head.List:Acc
- Accumulate a list of terms in the accumulatorAcc
List
- Accumulate a list of terms in the accumulatordcg
X/Acc
- UnifyX
with the left term for the accumulatorAcc
Acc/X
- UnifyX
with the right term for the accumulatorAcc
X/Acc/Y
- UnifyX
with the left andY
with the right term for the accumulatorAcc
insert(X,Y):Acc
- Insert the argumentsX
andY
into the chain implementing the accumulatorAcc
. This is useful when the value of the accumulator changes radically becauseX
andY
may be the arguments of an arbitrary relationinsert(X,Y)
- Insert the argumentsX
andY
into the chain implementing the accumulatordcg
. This inserts the difference list X-Y into the accumulated list
Predicates are declared with facts of the following form:
pred_info(Name, Arity, List)
The predicate Name/Arity
has the hidden parameters given in List
. The parameters are added in the order given by List
and their names must be atoms.
Accumulators are declared with facts in one of two forms. The short form is:
acc_info(Acc, Term, Left, Right, Joiner)
The long form is:
acc_info(Acc, Term, Left, Right, Joiner, LStart, RStart)
In most cases the short form gives sufficient information. It declares the accumulator Acc
, which must be an atom, along with the accumulating function, Joiner
, and its arguments Term
, the term to be accumulated, and Left
& Right
, the variables used in chaining.
The long form of acc_info
is useful in more complex programs. It contains two additional arguments, LStart
and RStart
, that are used to give default starting values for an accumulator occurring in a body goal that does not occur in the head. The starting values are given to the unused accumulator to ensure that it will execute correctly even though its value is not used. Care is needed to give correct values for LStart
and RStart
. For DCG-like list accumulation both may remain unbound.
Two conventions are used for the two variables used in chaining depending on which direction the accumulation is done. For forward accumulation, Left
is the input and Right
is the output. For reverse accumulation, Right
is the input and Left
is the output.
Passed arguments are conceptually the same as accumulators with =/2
as the joiner function. Passed arguments are declared as facts in one of two forms. The short form is:
pass_info(Pass)
The long form is:
pass_info(Pass, PStart)
In most cases the short form is sufficient. It declares a passed argument Pass
, that must be an atom. The long form also contains the starting value PStart
that is used to give a default value for a passed argument in a body goal that does not occur in the head. Most of the time this situation does not occur.
With ==>>
, you can also specifiy "guards" in the head.
To avoid confusion with "push back lists" for -->
, each guard
must be prefixed by the operator ?
.
Here's a trivial example:
p(A, X) -->> A=a, !, X=1.
can be written with guards as:
p(A), ? A=a ==>> {X=1}.
Because guards currently are not expanded, there is no need to use the
{...}
notation for guards; but you can use it if you want. Note
that SWI-Prolog's use of curly braces for dicts means that you need to
put a space between ?
and {
.
The standard definition of DCGs allows a "push-back list" or "right-hand context" in the head of a DCG rule. These seem to be of limited use, and primarily used for doing a "look-ahead". For some discussion on this, see this comment by Richard O'Keefe and the DCG Primer.
This comment by Richard
O'Keefe
discusses cuts in DCGs and why the original implementation used a
C/3
predicate for unifications. In essence, if you move a unification over a cut,
you end up with a non-steadfast predicate.
EDCGs short-cut this, so if you use cuts, you might not get a correct translation. Here's an example:
p(a), [X] --> !, [X,a], q(X).
This should be translated as
p(a, S0, S) :- !,
/* note that the cut is done *exactly* where it appears */
S0 = [X,a|S1],
q(X, S1, S2),
S = [X|S2].
The current SWI-Prolog implementation translates it to the following,
which has an extra =/2
in it:
p(a, S0, S) :-
!,
C=S0,
C=[X, a|S1],
q(X, S1, S2),
S=[X|S2].
Using SWI-Prolog 7.1 or later:
?- pack_install(edcg).
This module uses semantic versioning.
Source code available and pull requests accepted at http://github.com/kamahen/edcg (which takes over from http://github.com/mndrix/edcg).
@license mit
Peter Van Roy's page: Declarative Programming with State
Technical Report UCB/CSD-90-583 Extended DCG Notation: A Tool for Applicative Programming in Prolog by Peter Van Roy:
A short Wikipedia article on DCGs and extensions.