Seek library like dcg/basics with predicates returning difference list

Does a variation of the library dcg/basics exist with the predicates returning a difference list (partial list or open list) instead of a closed list?

Do you mean using phrase/3 instead of phrase/2?

Thanks, but no. :slightly_smiling_face:

Here is a preview of my current work toward what I seek.
string_without_partial_list(End,Codes,Hole) -->
	{
        string(End), !,
        string_codes(End,EndCodes)
	},
	list_string_without_partial_list(EndCodes,Codes,Hole).
string_without_partial_list(End,Codes,Hole) -->
	list_string_without_partial_list(End,Codes,Hole).

list_string_without_partial_list(Not,[C|T],Hole) -->
	[C],
	{ \+ memberchk(C,Not) }, !,
	list_string_without_partial_list(Not,T,Hole).
list_string_without_partial_list(_,Hole,Hole) --> [].
:- begin_tests(string_without).

control_dcg(Before) -->
    string_without("c",Before).

test(control_test) :-
    Input = "abcdef",
    string_codes(Input,Codes),
    DCG = control_dcg(Before),
    phrase(DCG,Codes,Rest),

    assertion( Codes == `abcdef` ),
    assertion( Before == `ab` ),
    assertion( Rest == `cdef` ).

partial_list_dcg(Partial_list,Hole) -->
    string_without_partial_list("c",Partial_list,Hole).

test(partial_list) :-
    Input = "abcdef",
    string_codes(Input,Codes),
    DCG = partial_list_dcg(Partial_list,Hole),
    phrase(DCG,Codes,Rest),
    write_term(Partial_list,[dotlists(true)]),

    assertion( Codes == `abcdef` ),
    assertion( Partial_list =@= [0'a,0'b,_] ),
    assertion( Hole =@= _ ),
    assertion( Rest == `cdef` ).

:- end_tests(string_without).

Also before it is pointed out, I know it is using and assertion/1 and probably should not. I did try the other day to this with the assertions with the test predicate, but could not figure out how to get it to work. An example of that would be nice but is not needed at the moment.

Personal notes and references

Notes:
This code uses DCGs which add a hidden accumulator for parsing the input, but also uses a another pair of state variables (accumulators). The SWI-Prolog package EDCG might be of use here. (GitHub)

  • insert(X,Y):Acc - Insert the arguments X and Y into the chain implementing the accumulator dcg . This inserts the difference list X-Y into the accumulated list

The code example given above is part of a larger example to pretty print a single line XML (as received by an Internet query (think XHTML)) into multiple lines by injecting indent spacing and new line sequences.

The code started out with a DCG to parse the XML then through a series of intermediate steps is working toward creating the pretty printed XML as a list of character codes with the list to be created not by appending closed list, but by filling the holes of the partial list.

One of the intermediate steps used format/3 with the output parameter

  • codes (-Codes, -Tail)

Intermediate step example.

:- multifile
error:has_type/2.

error:has_type(partial_list,L0) :-
    '$skip_list'(_, L0,L),
    var(L).

tag_end_03(_Spacing,Tag,Fragment,Hole0,Hole) -->
    "</",
    string_without(">",Tag_codes),
    { atom_codes(Tag,Tag_codes) },
    ">",
    { Fragment = ['</',Tag,'>\n'] },
    {
        format(codes(Open_list1,Hole1),'</~w>~n',[Tag]),
        dl_combine(Hole0,Open_list1),
        Hole = Hole1
    }.

difference_append(Open_list,Hole,Open_or_closed_list) :-
    must_be(partial_list,Open_list),
    must_be(list_or_partial_list,Open_or_closed_list),
    Hole = Open_or_closed_list.

dl_combine(Hole1,Open_list2) :-
    difference_append(_,Hole1,Open_list2).

As the code adds more intermediate steps, the predicates gain more arguments. The argument Fragment was an argument used with a previous intermediate step so can actually be removed with no effect to this example predicate. Since these are my notes I didn’t clean up the example.

Obviously that code is not very efficient because it calls dl_combine which can be factored out, but in doing the intermediate steps allows me to make changes without failing the test cases which keeps me headed down a valid path.

While there are many historical references and papers using the X-Y syntax with partial list (difference list or open list), I prefer the X and Y being passed as separate variables as noted in format/3


To see that a list is difference list use write_term/2, e.g.

?- write_term([a|H],[dotlists(true)]).
.(a,_618)
true.

?- write_term([a],[dotlists(true)]).
.(a,[])
true.

?- write_term([a|b],[dotlists(true)]).
.(a,b)
true.

Partial list end with a hole (variable), so only .(a,_618) is a partial list in the three examples above.


Some example predicates and unit test for difference list.


difference_append(Open_list,Hole,Open_or_closed_list) :-
    must_be(partial_list,Open_list),
    must_be(var,Hole),
    must_be(list_or_partial_list,Open_or_closed_list),
    Hole = Open_or_closed_list.

dl_combine(Hole1,Open_list2) :-
    difference_append(_,Hole1,Open_list2).

:- begin_tests(difference_list).

% This is here to allow a quick comparison of append/3
test(001) :-
    L1 = [a],
    L2 = [b],
    L3 = _,
    append(L1,L2,L3),

    assertion( L1 == [a]   ),          % NB L1    DID NOT change its value
    assertion( L2 == [b]   ),          % NB L2    DID NOT change its value
    assertion( L3 == [a,b] ).          % NB L3    DID     change its value

test(002) :-
    DL1 = [a|Hole1],
    DL2 = [b|Hole2],
    difference_append(DL1,Hole1,DL2),

    assertion( DL1   == [a,b|Hole2] ), % NB DL1   DID     change its value
    assertion( Hole1 == [b|Hole2]   ), % NB Hole1 DID     change its value
    assertion( DL2   == [b|Hole2]   ). % NB DL2   DID NOT change its value

% Demonstrates how to see a difference list as a dot list and output with a variable name for use with comparison
test(003) :-
    DL1 = [a|Hole1],
    DL2 = [b|Hole2],
    difference_append(DL1,Hole1,DL2),

    numbervars(DL1,0,_),
    with_output_to(atom(Dot_list),write_term(DL1,[numbervars(true),dotlists(true)])),

    assertion( DL1 == [a,b|Hole2] ),
    assertion( Dot_list == '.(a,.(b,A))' ).

test(004) :-
    L1 = [a,b,c|H1],
    L2 = [d,e,f|H2],
    L3 = [g,h,i|H3],
    dl_combine(H1,L2),
    dl_combine(H2,L3),

    assertion( L1 == [a,b,c,d,e,f,g,h,i|H3] ),
    assertion( H1 == [d,e,f,g,h,i|H3] ),
    assertion( L2 == [d,e,f,g,h,i|H3] ),
    assertion( H2 == [g,h,i|H3] ),
    assertion( L3 == [g,h,i|H3] ),
    assertion( H3 == H3 ).

% Notice that dl_combine(H1,L2) is the same as H1 = L2.
test(005) :-
    L1 = [a,b,c|H1],
    L2 = [d,e,f|H2],
    L3 = [g,h,i|H3],
    H1 = L2,
    H2 = L3,

    assertion( L1 == [a,b,c,d,e,f,g,h,i|H3] ),
    assertion( H1 == [d,e,f,g,h,i|H3] ),
    assertion( L2 == [d,e,f,g,h,i|H3] ),
    assertion( H2 == [g,h,i|H3] ),
    assertion( L3 == [g,h,i|H3] ),
    assertion( H3 == H3 ).

:- end_tests(difference_list).

References:
Extended DCG’s: Declarative Programming with State
write_term(X,[dotlists(true)]).
How to swap three by three elements in a prolog list? - Notice that instead of caring around two different sets of state variables, this uses one phrase/3 to deconstruct the input then a second phrase/3 to reconstruct a modified input. While this works for a the simple case, I don’t know how well or efficient it would be with a recursive case like XML. So if you seek a means to transform data using DCGs, there are other ways to go about it.