-
I was studying @triska 's Zurg implementation. Licking my wounds from the fair tree enumeration discussion, I thought I would try my hand at writing a counting DCG. I wrote the following: % count up move time
move_time(Moves, T) :-
phrase(move_time_(Moves), [0], [T]).
move_time_([]) --> [].
move_time_([Move|Moves]) -->
move_time_(Move),
move_time_(Moves).
move_time_(left_to_right(Toy1,Toy2)), [T1] -->
[T0],
{ toy_time(Toy1, Time1),
toy_time(Toy2, Time2),
T1 #= T0 + max(Time1,Time2) }.
move_time_(right_to_left(Toy)), [T1] -->
[T0],
{ toy_time(Toy, Time),
T1 #= T0 + Time }.
time_moves(T, Ms) :-
moves(Moves),
append(Ms, _, Moves),
move_time(Ms, T).
?- time_moves(T, Ms).
%@ T = 0, Ms = []
%@ ; T = 10, Ms = [left_to_right(buzz,woody)]
%@ ; T = 15, Ms = [left_to_right(buzz,woody),right_to_left(buzz)]
%@ ; ... . It works, I have no idea how or why it works. Now, I am absolutely baffled how it's possible that two declarations of I understand from the DCG Primer that the semicontext acts to push the term to the front of the phrase, but wouldn't that prevent the other rules from working that don't take the integer expression into account? It feels like the rules with semicontext notation are somehow passing information differently than the DCG rules which are not. I looked through the DCG source code but I can't even find a reference to semicontext 😅. |
Beta Was this translation helpful? Give feedback.
Replies: 1 comment 3 replies
-
😮 :- use_module(library(format)).
:- dynamic(move_time//1).
%% code from above, elided %%
?- listing(move_time_//1).
%@ move_time_([],A,B) :-
%@ A=B.
%@ move_time_([A|B],C,D) :-
%@ move_time_(A,C,E),
%@ move_time_(B,E,D).
%@ move_time_(left_to_right(A,B),C,D) :-
%@ C=[E|F],
%@ toy_time(A,G),
%@ toy_time(B,H),
%@ ( integer(I) ->
%@ ( integer(E),
%@ integer(G),
%@ integer(H) ->
%@ I=:=E+max(G,H)
%@ ; J is I,
%@ clpz:clpz_equal(J,E+max(G,H))
%@ )
%@ ; integer(E),
%@ integer(G),
%@ integer(H) ->
%@ ( true,
%@ var(I) ->
%@ I is E+max(G,H)
%@ ; K is E+max(G,H),
%@ clpz:clpz_equal(I,K)
%@ )
%@ ; clpz:clpz_equal(I,E+max(G,H))
%@ ),
%@ F=L,
%@ D=[I|L].
%@ move_time_(right_to_left(A),B,C) :-
%@ B=[D|E],
%@ toy_time(A,F),
%@ ( integer(G) ->
%@ ( integer(D),
%@ integer(F) ->
%@ G=:=D+F
%@ ; H is G,
%@ clpz:clpz_equal(H,D+F)
%@ )
%@ ; integer(D),
%@ integer(F) ->
%@ ( true,
%@ var(G) ->
%@ G is D+F
%@ ; I is D+F,
%@ clpz:clpz_equal(G,I)
%@ )
%@ ; clpz:clpz_equal(G,D+F)
%@ ),
%@ E=J,
%@ C=[G|J].
%@ true. |
Beta Was this translation helpful? Give feedback.
Or rather: Too much tracking of irrelevant details can easily obscure the actual ideas. One such case of obscuration is operationalizing language. Yes, everything will eventually be executed on a machine that does all kinds of things but this does not mean that it will be easy to follow all the details.
Semicontext is just such a beast. In fact, some call it operationalizingly push back lists and it took us quite some time to find a good descriptive non-operational name for it. It's a semicontext because a (right-) context needs a terminal on both sides, like in
p, [a] --> q, [a].
but it is only "half" of it. (H…