Translation to DCG Semicontext not working - follow on

断了今生、忘了曾经 提交于 2019-12-02 04:50:50

问题


As a follow up to this question which poses the problem

Return count of items in a list but if two identical items are next to each other then don't increment the count.

This code is the closest I came to solving this with DCG and semicontext.

lookahead(C),[C] -->
    [C].

% empty list
% No lookahead needed because last item in list.
count_dcg(N,N) --> [].

% single item in list
% No lookahead  needed because only one in list.
count_dcg(N0,N) -->
    [_],
    \+ [_],
    { N is N0 + 1 }.

% Lookahead needed because two items in list and
% only want to remove first item.
count_dcg(N0,N) -->
    [C1],
    lookahead(C2),
    { C1 == C2 },
    count_dcg(N0,N).

% Lookahead needed because two items in list and
% only want to remove first item.
count_dcg(N0,N) -->
    [C1],
    lookahead(C2),
    {
        C1 \== C2,
        N1 is N0 + 1
    },
    count_dcg(N1,N).

count(L,N) :-
    DCG = count_dcg(0,N),
    phrase(DCG,L).

What is the correct way to solve the problem using DCG with semicontext on the clause head?

Would like to know if the variation with the semicontext on the clause head is possible or not. If possible then working example code is desired, if not possible then an explanation is desired.


回答1:


I think this is using semi context notation correctly. I am counting using 0,s(0),...

% Constraint Logic Programming
:- use_module(library(dif)).    % Sound inequality
:- use_module(library(clpfd)).  % Finite domain constraints

list([])     --> [].
list([L|Ls]) --> [L], list(Ls).

state(S), [state(S)] --> [state(S)].
state(S, s(S)), [state(s(S))] --> [state(S)].

keep_state(S,I),[state(S)] --> [state(S)],[I].
end_state(S)  -->[state(S)],[].

lookahead(C),[S,C] -->
    [S,C].

count_dcg(S,S) --> 
    state(S), %might not need this
    end_state(S).

/* Can be used get the length of a list
count_dcg(S,S2) --> 
    state(S,S1),
    keep_state(S1,_),
    count_dcg(S1,S2),
    {}.
*/

%last item.
count_dcg(S,S1) -->     
    state(S,S1),
    keep_state(S1,_C),
    list(R),
    {R = [state(_)]}.

%Two the same dont increase state 
count_dcg(S,S1) -->
    state(S), %might not need this
    keep_state(S,C1),
    lookahead(C1),
    count_dcg(S,S1).

%Two different increase state  
count_dcg(S,S2)  -->
    state(S,S1),
    keep_state(S1,C1),
    lookahead(C2),
    {
        dif(C1,C2)
    },
    count_dcg(S1,S2).

count(L,S) :-
    phrase(count_dcg(0,S),[state(0)|L]).

This does not work as well as I hoped for cases like:

65 ?- count([a,b,X,c],L).
X = b,
L = s(s(s(0))) ;
;
X = c,
L = s(s(s(0))) .

You can convert peano with:

natsx_int(0, 0). 
natsx_int(s(N), I1) :- 
  I1 #> 0, 
  I2 #= I1 - 1, 
  natsx_int(N, I2).

or you can change the state predicates:

state(S), [state(S)] --> [state(S)].
state(S, S2), [state(S2)] --> [state(S)],{S2#=S+1}.



回答2:


How about:

:-use_module(library(clpfd)).

list([])     --> [].
list([L|Ls]) --> [L], list(Ls).

lookahead(C),[C] -->
    [C].

count_dcg(N,N) --> [].
count_dcg(N0,N) --> %last item.
    [_],
    list(R),
    {R = [], N #=N0+1}.
count_dcg(N0,N) -->
    [C1],
    lookahead(C1),
    count_dcg(N0,N).
count_dcg(N0,N) -->
    [C1],
    lookahead(C2),
    {
        dif(C1,C2),
        N1 #= N0 + 1
    },
    count_dcg(N1,N).

count(L,N) :-
    phrase(count_dcg(0,N),L).


来源:https://stackoverflow.com/questions/54986266/translation-to-dcg-semicontext-not-working-follow-on

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!