Package edcg needs module predicates to work, is there another abstraction level possible?

I was motivated by your speach to try it out for myself:


p(0,1).

q(1,2).

r(2,3).

s(1,3,4).

test003(START,RESULT) --> [PRED], { CALL=..[call,PRED,START,VALUE2], call(CALL)}, ({RESULT=VALUE2};test003(VALUE2,RESULT)).

/*

(ins)?- phrase(test003(0,RES), [p,q,r,s(1)],R).
RES = 1,
R = [q, r, s(1)] ;
RES = 2,
R = [r, s(1)] ;
RES = 3,
R = [s(1)] ;
RES = 4,
R = [] ;
false.

*/


:- use_module( library(edcg)).


edcg:acc_info(monad,PRED,In,Out,(CALL=..[call,PRED,In,Out],call(CALL))).

edcg:pred_info(test004,0,[dcg,monad]).

test004 -->> [PRED], !, [PRED]:monad, test004.
test004 -->> [].

/*
(ins)?- test004([p,q,r,s(1)],X,0,E).
X = [],
E = 4.

(ins)?- test004([p,q,r],X,0,E).
X = [],
E = 3.

(cmd)?- test004([p,q],X,0,E).
X = [],
E = 2.

(cmd)?- test004([p],X,0,E).
X = [],
E = 1.

(cmd)?- test004([],X,0,E).
X = [],
E = 0.
*/

edcg:pred_info(test005,0,[dcg,monad]).

test005 -->> [PRED], [PRED]:monad, test005.
test005 -->> [].

/*
(cmd)?- test005([p,q,r,s(1)],X,0,E).
X = [],
E = 4 ;
X = [s(1)],
E = 3 ;
X = [r, s(1)],
E = 2 ;
X = [q, r, s(1)],
E = 1 ;
X = [p, q, r, s(1)],
E = 0.
*/

edcg:pred_info(test006,0,[dcg,monad]).

test006 -->> [].
test006 -->> [PRED], [PRED]:monad, test006.

/*

(cmd)?- test006([p,q,r,s(1)],X,0,E).
X = [p, q, r, s(1)],
E = 0 ;
X = [q, r, s(1)],
E = 1 ;
X = [r, s(1)],
E = 2 ;
X = [s(1)],
E = 3 ;
X = [],
E = 4.

*/

(It is maybe not the full flavor of a monad, just a pipe, but also a good exercise.)

Edcg is indeed better readable than dcg.

Btw. is in dcg any possibility to enclose the list by another cons cell when I call another dcg predicate?

Normally I would write something like:

x ā†’ [A,B], {ā€¦}, y.

If R is the remaining list, y operates on R, but I want that y operates for instance on [A|R].

Is that possible?

Kind regards.

Iā€™ve only used it a few times in earnest, but itā€™s been extremely useful those times. Making it easier to use certainly seems to me like it would help improve a lot of otherwise-ugly code.

EDCG is a superset of DCG. In particular, thereā€™s a builtin accumulator dcg, so you can write:

edcg:pred_info(foo, 1, [dcg]).
edcg:pred_info(bar, 1, [dcg]).

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

and thatā€™s the same as if you had written

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

One big difference is that DCGs require {...} around goals that arenā€™t expanded whereas EDCGs require pred_info/3 specifications to be expanded. (See my workaround to this below.)

As for implementing EDCGs as an extension of DCGs ā€¦ that could get a bit tricky, with DCG expansion being a ā€œbuilt-inā€ thing. As @jan has said, term expansion itself has some problems (itā€™s a very old part of Prolog; there are multiple proposals about better ways of doing things (e.g., Logtalk has a different approach), and it might be better to first think about something better than term expansion first.


PS: I use this to catch cases where Iā€™ve forgotten to define a predicate:

% This definition of edcg:pred/3 catches all situations where there's
% a goal in a -->> or ==>> predicate that hasn't been specified and
% isn't wrapped in {...}.
edcg:pred_info(Name, Arity, Accs) :-
    (   pred_info_(Name, Arity, Accs)
    *-> true
    ;   Name == (!), Arity == 0
    ->  true
    ;   Name == call
    ->  true
    ;   throw(error(no_pred_info(Name/Arity), _))
    ).

and then use pred_info_/3 for specifying how accumulators are used.

This would be a great improvement, aligning with the usual syntax support provided by the compiler.

I found confusing the data flow (In/Out vs Out/In), but itā€™s not easy to suggest an alternative. Would be possible to add debugger support ? I think that otherwise could be a nightmare to follow complex algorithms where the data transformation is hidden away from sources.

edit

At least for some audience, maybe an improvement wrt the In/Out Out/in specification would be
inherited/syntetized attributes. Of course, this would introduce confusion when speaking of attvarsā€¦

Thanks for all the input. Essentially we have two issues: passing data through a network of predicates and dealing with accumulator variables (A0, A1, ā€¦ A). DCGs solve the latter problem for one accumulator variable which we can (mis)use using push back lists to a deal with a single state variable that we may choose to pass or update. ā€œNormalā€ languages with destructive assignment have less of a problem as they do not require accumulator variables but simply accumulate in a simple variable and they can combine all passed and accumulator variables in a struct/record/object/ā€¦

We have EDGC that allows us to create multiple accumulator pairs and passed variables. That is all nicely compiled away (I think), resulting in pretty much the same code as when done ā€œby handā€. The price is a lot of declarations, special access predicates for the hidden variables and a lot of infrastructure that will be required to keep all the IDE tools working as we are used to (at least those who use them :slight_smile: )

The alternative is to use e.g. dicts to group variables the same way as other languages. The main problem is the accumulators. We either need to create a new dict with the updated accumulators or we need to use destructive assignment on the dict. Both have their price.

Yet another alternative for accumulators that has been proposed is to use some annotation that is expanded into a pair of successive variables, For example, *A can mean A0,A1. Now we can do what DCGs do as e.g.

s(*L) :-
   q(*L),
   r(*L).

That is a reasonable solution to multiple accumulators IMO. Given enough variables we also want variable hiding or grouping (in a dict). Logtalk has parameterized objects for that which, AFAIK boils does to passing a compound with the parameters that have a mapping from name to position and a predicate that allows fetching some parameter by name (I guess translated to an arg/3 call on the parameter block). That doesnā€™t handle accumulators (correct me if Iā€™m wrong). It relates to an old proposal from GNU-Prolog to have module parameters.

In theory, I guess we can deal with accumulators inside a dict (or compound) by copying the dict before starting the code where the dict acts as hidden set of parameters and using b_set_dict/3 to update the accumulator. If passing variables and accumulators between calls is the only role played by the dict, assignment is fine. That will impose some slowdown. I donā€™t know whether that would be significant.

Somewhat related, Iā€™ve been thinking for a long time to allow passing data around ā€œhiddenā€, i.e., using a reserved VM register that will (probably) carry a dict around. Then you need primitives to access and modify this value. That requires some though about the required scope and update semantics. If it is feasible to define the appropriate primitives that would be a solution that requires only small changes to the VM without much (if any) effect on the IDE tools or general transparency of the system. Portability is feasible using a rewrite similar as Logtalk uses to add its context parameters. Is that worth exploring?

This sounds like one of the ways I think of EDCGs. With most procedural programming languages I think of the the memory as being segmented at a high level into the stack and heap. Then the heap is segmented into data structures that can live independent of the stack.

With EDCGs I think of them as a way to segment memory into more stacks and/or use it as a heap. When used as a heap it becomes apparent that EDCGs can be used to simulate other data structures. Then one realizes that EDCGs do not come out of the box with these other types of data structures and so they have to be created as needed.

In short, EDCGs creates the hidden code that translates high level data structures into Prolog so that one does not have to manage all of the data structures known to an EDCG in each clause of a predicate.

Is this thinking along the lines of what you are thinking?

Mercury has the ! operator for that. I would appreciate that feature.

1 Like

You will get scolded by the ISO core standard orthodoxy fighters. As soon as
! is a prefix, according to the orthodoxy fighters, whos names I do not want
to mention, you have to write (!) in your ordinary code, for the ordinary cut.


(ins)?- op( 5, fx, '!').
true.

(ins)?- A=!B.
A = !B.

Seems to work.

But that was not my idea. I meant this principle to represent 2 variables by one in general.

I mean the implementation would be a change in the syntax anyway. But if we are already there - I would also like to have a way to accommodate s-expressions in terms: TERM = (+ 2 3 4). (I guess I cannot define the space as an operator.)

Iā€™ve started some work on adding debugger support, by improving the term_expansion/4 rules. But itā€™s very much a work-in-progress and I donā€™t have much time to work on it right now. (Itā€™s on the te4 branch but I havenā€™t committed my latest stuff to github)

If someone wants to work on this, please contact me. I donā€™t use the debugger much because writeln/1 often suffices for me, so I donā€™t have a lot of personal incentive, and I have some higher priority things to deal with first.

Yes and no. It works, but it has an annoying side effect, for the ordinary cut.
Try Scryer Prolog and an example with ordinary cut, after you made ! prefix.
Also GNU Prolog will bark, not only Scryer Prolog:

/* GNU Prolog 1.4.5 (64 bits) */
?- op(200,fy,!).

?- [user].
p(a) :- !.
user:1:10: syntax error: expression expected or previous operator needs brackets

SWI-Prolog is more flexible:

/* SWI-Prolog (threaded, 64 bits, version 8.5.1) */
?- op(200,fy,!).

?- [user].
p(a) :- !.
p(b) :- !.
^D

?- p(X).
X = a.

Thanks Peter, I will take a look, but right now Iā€™m out of spare timeā€¦

I have a dreamā€¦ a trace on steroids that put to good use the amount of spare memory on today desktops, and presents the information not only as a (proof) tree, but also with other graphs, displayed with web techā€¦

EDCGs could be a good testbed, I hope to find the time & energy to show somethingā€¦

1 Like

More for your list

  • Trace through constraint rules.
  • Trace back through a term rewrite to the original source code. This would be very hard.
  • Allow the graphical tool to expand and contract parts of the graph. (think fish eye)
  • Do time travel debugging.
  • Show the edges not just as one call but as multiple calls when backtracking and processing a predicate with new values. The other option is to show each predicate call to a separate node but that grows the graph size quickly for solutions that have lots of different answers.
  • Show use of aggregates as Euler diagram and not as logic calls. Would be a side panel.
  • Step into C level code.
  • Work with non-logical code, e.g. global variables and such.