Calling call//1 makes DCG nonfunctional? (+ "difference list" in DCGs vs. "difference list" for appending)

So, I have had this problem earlier and Eric tried to help but I wanted to get to the bottom of this.

Task: Recognize the substrings ab and ba in an input string, and also:

  • Count them
  • Create a string that describes how the input string was cut up into substrings

The solution (which was completely wrong in my previous post because I hadn’t understood semicontext notation):

I started with a regex, which means finite state machine, which leads to:

and thus an implementation as DCG:

:- use_module(library(clpfd)).

:- debug(dcg). % switch on debugging output for topic "dcg"

% ---
% merge(+XX, +Chars, +PiecesIn, -PiecesOut)
% ---

merge_cs(XX,[C|Cs],FPs,[A,XX|FPs]) :- reverse([C|Cs],Csr), atom_chars(A,Csr).
merge_cs(XX,[]    ,FPs,[  XX|FPs]).

merge_cs([C|Cs],[A]) :- reverse([C|Cs],Csr), atom_chars(A,Csr).
merge_cs([]    ,[]).

ex_debug(Format,Args,HiddenLeft,HiddenRight). 
/*
 :-  
   atomic_list_concat(["~q ~q :", Format],'',NewFormat),
   debug(dcg,NewFormat,[HiddenLeft,HiddenRight|Args]).
*/

% ---
% The DCG
% ---

start(AB,BA,Pieces) --> 
   [], 
   % call(ex_debug("start->anything",[])),
   { 
      debug(dcg,"start->anything",[])
   }, 
   anything(AB,BA,Pieces,[]).

anything(AB,BA,PiecesOut,Cs) --> 
   [a,b], !,
   { 
      debug(dcg,"ab: anything->start",[]), 
      AB #= ABn+1, 
      merge_cs(ab,Cs,FuturePieces,PiecesOut)
   }, 
   start(ABn,BA,FuturePieces).

anything(AB,BA,PiecesOut,Cs) --> 
   [b,a], !,
   {
      debug(dcg,"ba: anything->start",[]), 
      BA #= BAn+1, 
      merge_cs(ba,Cs,FuturePieces,PiecesOut)
   },
   start(AB,BAn,FuturePieces).

anything(AB,BA,Pieces,Cs) -->
   [C], !,
   {
      debug(dcg,"~q: anything->anything",[C])
   },
   anything(AB,BA,Pieces,[C|Cs]).

anything(0,0,Pieces,Cs) -->
   [],
   {
      debug(dcg,"anything->end",[]),
      merge_cs(Cs,Pieces)
   }.

% ---
% Calling the DCG
% ---

fsm_parse(Str,AB,BA,Dashed,Rest) :- 
   atom_chars(Str,Cs),
   phrase(start(AB,BA,Pieces),Cs,Rest),
   atomic_list_concat(Pieces, '-', Dashed).

% ---
% Tests
% ---

:- begin_tests(dcg_chars).

test(fsm_00,[true(T),nondet]) :- fsm_parse(''                ,AB,BA,D,[]), T = ([AB,BA,D] == [0,0,'']).
test(fsm_01,[true(T),nondet]) :- fsm_parse('bab'             ,AB,BA,D,[]), T = ([AB,BA,D] == [0,1,'ba-b']).
test(fsm_02,[true(T),nondet]) :- fsm_parse('aba'             ,AB,BA,D,[]), T = ([AB,BA,D] == [1,0,'ab-a']).
test(fsm_03,[true(T),nondet]) :- fsm_parse('yyabyybayy'      ,AB,BA,D,[]), T = ([AB,BA,D] == [1,1,'yy-ab-yy-ba-yy']).
test(fsm_04,[true(T),nondet]) :- fsm_parse('yyabbayyabaabaab',AB,BA,D,[]), T = ([AB,BA,D] == [4,1,'yy-ab-ba-yy-ab-a-ab-a-ab']).
test(fsm_05,[true(T),nondet]) :- fsm_parse('abbaayybbaba'    ,AB,BA,D,[]), T = ([AB,BA,D] == [1,3,'ab-ba-ayyb-ba-ba']).
test(fsm_06,[true(T),nondet]) :- fsm_parse('abbaabbaba'      ,AB,BA,D,[]), T = ([AB,BA,D] == [2,3,'ab-ba-ab-ba-ba']).
test(fsm_07,[true(T),nondet]) :- fsm_parse('abbayyabbaba'    ,AB,BA,D,[]), T = ([AB,BA,D] == [2,3,'ab-ba-yy-ab-ba-ba']).
test(fsm_08,[true(T),nondet]) :- fsm_parse('abbaabbaba'      ,AB,BA,D,[]), T = ([AB,BA,D] == [2,3,'ab-ba-ab-ba-ba']).
test(fsm_09,[true(T),nondet]) :- fsm_parse('yabybayyyy'      ,AB,BA,D,[]), T = ([AB,BA,D] == [1,1,'y-ab-y-ba-yyyy']).
test(fsm_10,[true(T),nondet]) :- fsm_parse('yyyyyyyyya'      ,AB,BA,D,[]), T = ([AB,BA,D] == [0,0,'yyyyyyyyya']).
test(fsm_11,[true(T),nondet]) :- fsm_parse('yyyyyyybaa'      ,AB,BA,D,[]), T = ([AB,BA,D] == [0,1,'yyyyyyy-ba-a']).
test(fsm_12,[true(T),nondet]) :- fsm_parse('yyyyyyyba'       ,AB,BA,D,[]), T = ([AB,BA,D] == [0,1,'yyyyyyy-ba']).
test(fsm_13,[true(T),nondet]) :- fsm_parse('yaybyayba'       ,AB,BA,D,[]), T = ([AB,BA,D] == [0,1,'yaybyay-ba']).
test(fsm_14,[true(T),nondet]) :- fsm_parse('yaabby'          ,AB,BA,D,[]), T = ([AB,BA,D] == [1,0,'ya-ab-by']).

:- end_tests(dcg_chars). 

rt(dcg_chars) :- run_tests(dcg_chars).

The above works perfectly well, just run rt(_) for great testing.

But now, note the commented-out line

% call(ex_debug("start->anything",[])),

in the first DCG rule. This is call//1 and it is supposed to call ex_debug/4 with the hidden list arguments of the DCG (supposing the DCG is implemented that way in the first place). This trick is mentioned in Markus Triska’s DCG Primer

Well, if you uncomment this line and run the program, it never terminates. call//1 seems to reset those lists, even if ex_debug/4 doesn’t do anything.

So:

  • Is call//1 sanely supported in SWI-Prolog?
  • If yes, where is the problem in the code above?

I’ll give you a hint:

[user].
foo(X) --> {bar(X)}.
^D
?- listing(foo).
foo(A, C, B) :-
    bar(A),
    B=C.

You can also look at the generated code for, e.g. foo-->[].

1 Like

Thanks Peter.

Got it. It’s not because the arguments are supposed to be threaded through:

start//3 without the call//1

?- listing(start).
start(AB, BA, Pieces, A, B) :-
    debug(dcg, "start->anything", []),
    C=A,
    anything(AB, BA, Pieces, [], C, B).

start//3 with the call//1

?- listing(start).
start(AB, BA, Pieces, A, B) :-
    call(ex_debug("start->anything", []), A, C),
    debug(dcg, "start->anything", []),
    D=C,
    anything(AB, BA, Pieces, [], D, B).

evidently. ex_debug/2 must at least do:

ex_debug(Format,Args,H,H).

so that H is treated-through w/o any modification or uninstantiation.

The leads me to some confusion regarding terminology:

The above “threading pattern” is generally called “using an accumulator” because

f(+AccIn,?AccOut)

accumulates a solution starting from AccIn as calls progress, and the result of the accumulation is unified with AccOut.

In "Extended DCG notation: A tool for applicative programming in Prolog", Peter van Roy writes:

An important Prolog programming technique is the accumulator (Sterling & Shapiro 1986). The DCG notation implements a single implicit accumulator. For example, the DCG clause:

term(S) --> factor(A), [+], factor(B), {S is A+B}.

is translated internally into the Prolog clause:

term(S,X1,X4) :- factor(A,X1,X2), X2=[+|X3], factor(B,X3,X4), S is A+B.

Each predicat is given two additional arguments. Chaining together these arguments implements the accumulator.

But sometimes, this is also called “difference lists”, IMHO incorrectly:

In particular, the SWI Prolog Manual states:

Grammar rules form a comfortable interface to difference lists

And from Markus Triska’s DCG Primer:

Each respective pair of additional arguments describes a so-called list difference.

In the literature, you will also encounter the term “difference list”. However, this terminology is
misleading: We are not talking about—as the name may suggest—a special kind of list. The
additional arguments are completely ordinary lists. It is their differences that matter especially
in such cases.

I always thought “Difference List” or “List Difference” describes the pattern whereby one holds two variables into the same list, one variable bound to the list head, and one variable bound to its (possibly open) tail - in order to append easily.

Here, we have just two lists. One could say that what happens in the DCG makes up the difference between AccIn and AccOut, but that’s reaching a bit.

These are really two very different “Difference Lists”…

Can you give some code with examples as unit test to show the difference?

For me there are

  1. list - which are closed list and end with [].

  2. difference list using two separate variables - where the second variable is unbound until bound with a new difference list of two separate variables but then for the new difference list the second variable becomes the second unbound variable of the difference list bound to the second variable of the first difference list. I have a graphic of this but I don’t know where it went; might have meet the circular file. These are the form used with DCG and EDCG. With these I tend to think of the two variables holding pointers with all of the operations with these as just pointer manipulation which is what makes them so fast; you never have to copy strings.

  3. difference list where the first variable holds a complete list and the second variable holds a subset of the end of the complete list. These I don’t use other then with examples and have not found a use for them outside of examples. These might not even be a separate type of difference list but I just can not reason with them in my mind as I don’t have a unified view of difference list that incorporates this concept.

  4. difference list using a pair, e.g. A-B. - For me these are just a different syntax representation of 2 but keep the two variables together. In debugging EDGC at times I wished EDCG used these.

I am currently considering switching from 2 to 4 when not using DCG and EDCG based on this post. However since 2 is ingrained with DCG and EDCG will use that form when required.

EDIT

Found the graphic but because it was highlighted in color so it needs to be scanned in color to see correctly and that shoots the size of the file into the 10 of millions of bytes which for a storage to knowledge ratio is way to low. Someday I plan to do some of these using GraphViz but not for the foreseeable future.

EDIT

In Difference Lists by Frank Pfenning on page L11.5

Seasoned Prolog hackers will often break up an argument which is a difference list into two top-level arguments for efficiency reasons.

1 Like

No … it’s a terminology issue.

If the pattern is an “accumulator pattern” (aka threading), one should call it that. Not call it a difference list.

Like this:

process(AccIn,AccOut) :- 
   process1(AccIn,AccOutMid1), 
   process1(AccOutMid1,AccOutMid2), 
   process1(AccOutMid2,AccOut).

Then caller would either leave the 2nd variable fresh or bind it to a desired final. Like so:

wants_to_see_the_result(In,Out) :- process(In,Out).
demands_that_result_be_empty(In) :- process(In,[]).

That’s what we see in DCGs.

If I understand Point 2 correctly, that’s the “difference list” used for “easy appending”, where you have code like this:

% Starter. predicate. "Data" is a list to append to a difference list,
% "Result" is the result of the appending, and is supposed to be
% equal to Data after the call. But one cannot call "dl_do(Data,Data)"
% that would seize up the computation.

dl_do(Data,Result) :- dl_append_all(Data,Result-Result).

% The recursion. The first clause appends aother iten "X" from "Data",
% the second "closes" the difference list when the end of "Data" has been
% reached.

dl_append_all([X|Xs],DL) :- 
   dl_append(X,DL,DLlonger),
   dl_append_all(Xs,DLlonger).
   
dl_append_all([],_-[]). 

% Appending a single item to the difflist can be done in a single fact
% using assembling/disassembling.

dl_append(X,Tip-[X|NewFin],Tip-NewFin). 

% Unit tests

:- begin_tests(difflist).

test(one, true(R=[1,2,3])) :- dl_do([1,2,3],R).
test(two, true(R=[]))      :- dl_do([],R).
   
:- end_tests(difflist).

rt :- run_tests(difflist).

These are NOT seen in DCGs.

Point 3 doesn’t evoke an image.

Point 4 is indeed just syntax.

My point is: DCGs use the accumulator pattern. They do NOT use the difference list pattern (vulgo, “use difference lists”). These things are not the same and should be kept clearly separate.

Nope, sorry, have to disagree. :ok_hand:

The accumulator pattern is doing the pointer manipulation the same as the difference list.

This reminds me of Einstein’s equivalence principle.

But they are not the same at all. The accumulator pattern isn’t beholden to any append operation or to any particular relationship between In and `Out:

process(AccIn,AccOut) :- 
   process1(AccIn,AccOutMid1), 
   process2(AccOutMid1,AccOutMid2), 
   process3(AccOutMid2,AccOut).

process1([_,_|R],[1|R]), 
process2(_,[a,b,c]).
process2(X,Y) :- reverse(X,Z),append(X,Z,Y).

Here is Frank Pfenning on difference lists:

https://www.cs.cmu.edu/~fp/courses/lp/lectures/11-diff.pdf

That’s NOT what is used in DCGs. At least I don’t see it.

Maybe the terminology accidently drifted over the years, I don’t know.

I plan to reply to this but it could take me hours (research) and I have some task to do soon.

A couple of thoughts …

You usually don’t need to hand-code a DCG clause … the {...} construct lets you call non-DCG predicates. But you want to display the “hidden” parameters, which can be found by this:

hidden(L, L, L).

and then your ex_debug would be (untested code):

ex_debug(Format,Args) -->
    hidden(Hidden),
    {atomic_list_concat(["~q ~q :", Format],'',NewFormat)},
    {debug(dcg,NewFormat,[HiddenLeft,HiddenRight|Args])}.

(With the EDCG formalism, you can access the hidden accumulators using the “/” notation.)

As for accumulators vs difference lists: the accumulators could use regular list append but for efficiency, they use difference lists. An accumulator can have a “null” accumulation, which is written [] (e.g., foo --> []). This becomes expanded to append([], HiddenLeft, HiddenRight), which is equivalent to HiddenLeft = HiddenRight.

Another way of looking at this is you could use regular lists for DCGs, with a different expansion that’s less efficient. For example:

foo(X) --> [X], bar.

would expand to

foo(X, L0, L2) :-
    append([X], L0, L1),
    bar(L1, L2).

Hope this helps and doesn’t further confuse things.

1 Like

let me digest this. Everyone seems to be aware of EDCGs btw, I’m barely aware of DCGs. Are they commonly used?

Who is everyone.

I know that Peter knows them and introduced me to them but I don’t see many others using them.

accumulator pattern -
In reading “The Craft of Prolog” by Richard A O`Keefe (WorldCat) it is noted as accumulator passing so I will go with that. Still working on a more formal description of this thus the book.

difference list pattern - I now better understand what a difference list is after having created a has_type/2 for it (ref), but for your use of the word pattern I have not found a formal description. At present I don’t know exactly how to interpret that.

My plan of trying to resolve this is to build up solid understandings of each concept independently then to see if they are equivalent or not; thus the note about the equivalence principle. I will probably switch to a pointer model and show that both concepts are the same by using pointer models.

EDIT

In working up to the pointer models did this which should be just as convincing without needing to do all of the graphics to show the pointers.

Details
% "Difference list" by Frank Pfenning page L11.4
% Difference list version
reverse(Xs, Ys) :-
    rev_1(Xs, (Ys-[])).
rev_1([X|Xs], (Ys-Zs)) :-
    rev_1(Xs, (Ys-[X|Zs])).
rev_1([], (Ys-Ys)).

% "Difference list" by Frank Pfenning page L11.4
% Difference list version
% Difference list as two parameters
reverse_2(Xs, Ys) :-
    rev_2(Xs, Ys,[]).
rev_2([X|Xs], Ys,Zs) :-
    rev_2(Xs, Ys,[X|Zs]).
rev_2([], Ys,Ys).

% "Difference list" by Frank Pfenning page L11.4
% Difference list version
% Difference list as two parameters
% with variables renamed
reverse_3(List, Reverse) :-                 % Rename Xs -> List, Ys -> Reverse
    rev_3(List, Reverse,[]).
rev_3([Head|Tail], Reverse0,Reverse) :-     % Rename X -> Head, Xs -> Tail, Ys -> Reverse0, Zs -> Reverse
    rev_3(Tail, Reverse0,[Head|Reverse]).
rev_3([], Reverse,Reverse).                 % Rename Ys -> Reverse

% "Difference list" by Frank Pfenning page L11.4
% Difference list version
% Difference list as two parameters
% with variables renamed
% with predicates reordered
reverse_4(List, Reverse) :-
    rev_4(List, Reverse,[]).
rev_4([], Reverse,Reverse).
rev_4([Head|Tail], Reverse0,Reverse) :-
    rev_4(Tail, Reverse0,[Head|Reverse]).

% "Difference list" by Frank Pfenning page L11.4
% Difference list version
% Difference list as two parameters
% with variables renamed
% with predicates reordered
% with arguments reordered
reverse_5(List, Reverse) :-
    rev_5(List, [],Reverse).
rev_5([], Reverse,Reverse).
rev_5([Head|Tail], Reverse0,Reverse) :-
    rev_5(Tail, [Head|Reverse0],Reverse).

% "The Craft of Prolog" by Richard A. O`Keefe page 22
% Accumulator passing version
% Compare this to reverse_5/2 which started out using difference list.
rev(List,Reverse) :-
    rev(List,[],Reverse).

rev([],Reverse,Reverse).
rev([Head|Tail],Reverse0,Reverse) :-
    rev(Tail,[Head|Reverse0],Reverse).

:- begin_tests(reverse).

reverse_test(1,[],[]).
reverse_test(2,[a],[a]).
reverse_test(3,[a,b],[b,a]).
reverse_test(4,[a,b,c],[c,b,a]).
reverse_test(5,[a,b,c,d],[d,c,b,a]).

test(reverse,[forall(reverse_test(_,Forward,Reverse))]) :-
    reverse(Forward,Reverse).

test(reverse_2,[forall(reverse_test(_,Forward,Reverse))]) :-
    reverse_2(Forward,Reverse).

test(reverse_3,[forall(reverse_test(_,Forward,Reverse))]) :-
    reverse_3(Forward,Reverse).

test(reverse_4,[forall(reverse_test(_,Forward,Reverse))]) :-
    reverse_4(Forward,Reverse).

test(reverse_5,[forall(reverse_test(_,Forward,Reverse))]) :-
    reverse_5(Forward,Reverse).

test(rev,[forall(reverse_test(_,Forward,Reverse))]) :-
    rev(Forward,Reverse).

:- end_tests(reverse).

Example run

?- run_tests(reverse).
% PL-Unit: reverse ................................... done
% All 35 tests passed
true.

** EDIT **

In working on the images with the pointer models thought of this question.

Where is it factually stated that the pair of a difference list have to be kept together in the same clause? In other words can you pass just one of the pair around to other predicates/clauses and still have an effective difference list?

1 Like

This is a comment about the PDF you linked. The “queue” example presented early in this lecture is a bastardized version of the same example from “The Craft of Prolog” by Richard O’Keefe, without attribution. Using a “difference list” like that to implement a queue certainly predates both, but the way the text is written (order of examples, considerations, improvements and so on) is copied 1:1. The text and code are re-written though.

I’m using the “pattern” word in the way it is used in other programming languages as “the general design principles of solving a given problem in a particular way”: Software design pattern - Wikipedia - I can’t believe I went to school when this little idea didn’t exist yet (snicker snicker … neither did unit tests)

Here is Stuart Sierra on Patterns in Clojure:

Actually, maybe one should use the word “idiom”, at 04:30

smaller patterns that are seen in a particular programming language

Anyway, the “accumulator pattern” is mentioned on page 20 of the Slideshow, which you can download at the above link:

It’s at 13:40.

Not matching fully what I have in my mind.

Where is it factually stated that the pair of a difference list have to be kept together in the same clause? In other words can you pass just one of the pair around to other predicates/clauses and still have an effective difference list?

Relax. “Factual statements” in Computer Science don’t hold for long. It’s just engineering, creative destruction and clarification is the lifeblood of all of that. Theoretical CS is different of course.

  • If you understand “difference list” (the DCG difference list) as a pair “Input list” and “Output list”, where “Output list” has been constructed by removing/adding elements from/to the front of input list, then yes: It makes scant sense to just pass one of the pair … unless you just want to operate on the “Input” or the “Output” independently and get back to a state where “nothing really happened” as no modifications are retained. (Note that in this pattern, the calls to clauses can be chained by “,” or there can be a recursive call passing the pair)

  • If you understand “difference list” as a pair “head of open list” (arg1) and “as-yet-uninstantated end of open list” (arg2) then yes again: It actually makes even less sense to operate on one of the pair independently because the idea is that: you create a new context (i.e. perform a recursive call) where arg1 and arg2 may have changed but still describe a valid “open-end difference list” (Note that in this pattern, the calls to clauses cannot be chained by “,” there must be a recursive call)

I took some time earlier this year to illustrate the “difference list” understood as “design pattern to easily append to a list (or maybe a tree) in Prolog-style logic programming” but it’s still hard to understand:

https://github.com/dtonhofer/prolog_notes/tree/master/difflists

In my understanding when the word pattern is used with coding one would expect to be able to find a name for the pattern, for which you have one - difference list pattern, a description of what it solves, which I am guessing is appending and a recipe that gives steps on how to solve it which I am guessing is in section Graphing the data structure.

If this is correct it should be made more clear as I had to grab the different parts from different sources. :slightly_frowning_face:

If that is correct, I still do not understand the difference between difference list pattern and accumulator passing. :slightly_frowning_face:

Well, considering the Frank Pfenning has a different text and different examples and there are only so many ways to introduce queues, and the text is far more extensive (an advantage of not being bound by page-limited books). I don’t really see the copying, 1:1 or otherwise. We all stand on the shoulders of the first books, right?

In “The Craft of Prolog”, I have found:

page 21 ff: “Accumulator Passing”

For some reason illustrated with LISP that uses setq and while, which is off-putting; why that style?. This is the “accumulator” as used in DCGs.

a technique called accumulator passing where the function or predicate receives
as arguments the current values of the variables, and returns, amongst other things,
the new values of the variables. Here is an example …

page 32 ff.: “Difference Lists”

A common thing to do in Prolog is to carry around a partial data structure and some of
the holes in it. To extend the data structure, you fill in a hole with a new term which has some
holes of its own. (Of course, you have to remember where the holes are!) … Difference lists are
a special case of this technique, where the two arguments weare passing around are positions
in a list.

This is not further elucidated and let the reader hang a bit as there is a digression on Reynolds diagrams, but then there is

page 42 ff: “A Digression on Queues”

which says:

A basic set of operations is

  • empty_queue(Queue) true when Queue represents an empty queue.
  • queue_head(Head, Queue1, Queue0) true when Queue1 and Queue0 represent
    queues having the same elements, except that Queue0 has an extra element at the left,
    namely Head
  • queue_last(Last, Queue1, Queue0) true when Queue1 and Queue0 represent queues
    having the same elements, except that Queue0 has an extra element at the right, namely
    Head [error, should be Last]

and

There is a technique well-known in functional programming circles. What you do is keep a
back-to-back pair of lists L+R, where the sequence represented by the pair is the sequence
represented by the list append(L,reverse(R)). With this representation, we have …

and later

Another approach would be to use difference lists. We might represent a queue by a pair
Front-Back, where Back is a tail of Front (this is in general a bad idea; difference lists should
almost always be represented by a pair of arguments, not by a data structure.) The code we
obtain is

empty_queue_3(Queue-Queue).                                  
queue_head_3(Head, Front-Back, [Head|Front]-Back).
queue_last_3(Last, Front-[Last|Back], Front-Back).      

This has some disadvantages, such as the fact that it is possible to remove more elements from
such a queue than were inserted into it. I call this hallucinating; logical variables let you refer
to terms that are not fully known yet, but when you take more things off a queue than are ever
entered you are dealing with things which will never exist.

That’s what I would call the Difference List approach/pattern/idiom.

At the beginning of the chapter it notes

In particular, there are several things you ares used to in conventional languages like Pascal and Lisp which Prolog doesn’t do in exactly the same way, but can do with procedure calls and argument passing, and there are some things which Prolog can do easily that Pascal can’t.

Yeah, but I mean, why not just do a recursive call, instead of messing around with a while and a setq, which is rather nonfunctional.

I suppose Richard also made an error when he wrote on page 21:

In the imperative language Lisp, we would code it the same way:

(defun len (X)
   (let ((N 0))
        (while (consp X)
             (setq N (1+ N))
             (setq X (cdr X)))
         N))

I suppose he meant “in LISP, used in imperative style…”.

You are taking parts of this out of context, you really need to read the chapter as a whole. In other words this is not a reference book it is a book for reading and learning.


On a side note the section on Difference List was not clear on a first reading for me; even now that section still has me confused on how to understand it. I did see the Reynolds diagram and could not find more about them with Google a few days ago which was surprising.

Here is another question for which I had to resolve when doing more research related to difference list, DCG and accumulator passing.

When a DCG is written as a recognizer does it use accumulator passing?

A recognizer is a predicate that either recognizes a sequence or not. So when created using phrase/2 it would look like this

example :-
    Input = "abc",
    DCG = zero_or_more_letters_recognizer,
    string_codes(Input,Codes_in),
    phrase(DCG,Codes_in).

zero_or_more_letters_recognizer -->
    [H],
    { between(0'a,0'z,H) },
    zero_or_more_letters_recognizer, !.
zero_or_more_letters_recognizer --> [].

For a recognizer the DCG does not return a value.

Example of DCG returning a value

zero_or_more_letters(Value)

Example of DCG not returning a value. This is used with a recognizer.

zero_or_more_letters

My answer

No

If you said Yes then think about why the word accumulator is part of accumulator passing. The way I came to my answer was to understand each line from running the example with trace/0.