Difference List

How to: Difference List

Note: This is a work in progress. When it is complete these notes will be removed.

Note: Do not reply to this topic. Questions, concerns, comments, etc. are to handled in
Wiki Discussion: Wiki: How to - Difference List

Note: This is just to get the topic started and hopefully others to jump in and make this useful. Even if you are brand new to Prolog, this is such a basic and fundamental concept that you can and should join in to help improve the value of this Wiki. Join the discussion at Wiki Discussion: Wiki: How to - Difference List

Note: This is a wiki and if you have Trust level: Basic you can edit this by clicking on the pencil icon in the lower right. Capture
These topics also have history so they can be rolled-back if needed.

References:

“The Craft of Prolog” by Richard A. O`Keefe (WorldCat) Section 1.5 - Difference Lists

Difference lists in Prolog by Attila Csenki
Difference Lists by Frank Pfenning
Open Lists and Difference Lists by Paul Brna

Learn Prolog Now! Chapter 7 Definite Clause Grammars by Patrick Blackburn, Johan Bos and Kristina Striegnitz
Common version
Testing version - using SWISH
Early version

Amzi - Difference List
Wikipedia DCG
WikiBooks

Difference list in other programming languages

Mercury - DCG
F# - DList
Haskell - Difference list
OCaml - DList


Difference list go by a few other names such as open list or partial list and what most Prolog programmers refer to as list are also known as closed list or proper list.

A closed list always ends with [] but a partial list always ends with an unbound variable. The unbound variable that ends a partial list is sometimes called a hole.

There are also lazy list. A lazy list is a list whose tail is an attributed value and when you unify against the tail the lists gets longer (and will either terminate in or in a new attributed variable). (ref).

Concrete list is probably a closed list but it is not well defined. (ref)


In learning to use partial list having a type check is handy. Here is the code to type check that a value is a partial list.

:- multifile
error:has_type/2.

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

Test case that help to illustrate the differences between a closed list and an open list.

:- begin_tests(list_info).

dot_list_test_case_generator( _      , 'A'            , open   ).  % Hole            % Base case
dot_list_test_case_generator( [_|_]  , '.(A,B)'       , open   ).  % .(A,Hole)
dot_list_test_case_generator( [_,_|_], '.(A,.(B,C))'  , open   ).  % .(A,.(B,Hole))
dot_list_test_case_generator( [a|_]  , '.(a,A)'       , open   ).  % .(a,Hole)
dot_list_test_case_generator( [a,b|_], '.(a,.(b,A))'  , open   ).  % .(a,.(b,Hole))
dot_list_test_case_generator( []     , '[]'           , closed ).  %                 % Base case
dot_list_test_case_generator( [_]    , '.(A,[])'      , closed ).  %
dot_list_test_case_generator( [_,_]  , '.(A,.(B,[]))' , closed ).  %
dot_list_test_case_generator( [a]    , '.(a,[])'      , closed ).  %
dot_list_test_case_generator( [a,b]  , '.(a,.(b,[]))' , closed ).  %

test(001,[forall(dot_list_test_case_generator(List,Expected_dot_list,_))]) :-
    numbervars(List,0,_),
    with_output_to(atom(Dot_list),write_term(List,[numbervars(true),dotlists(true)])),

    assertion( Dot_list == Expected_dot_list ).

test(002,[forall(dot_list_test_case_generator(List,_,Expected_list_type))]) :-
    (
        is_of_type(partial_list,List)
    ->
        List_type = open
    ;
        List_type = closed
    ),
    assertion( List_type == Expected_list_type ).

:- end_tests(list_info).

% This is the classic difference list append but with type checking added.
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.

% This predicate is useful in learning how to use difference list.
% This is often not seen in code because it can be replaced with 
%    Hole = Open_list
dl_combine(Hole,Open_list) :-
    difference_append(_,Hole,Open_list).

% Create closed list given open list.
open_closed_list(Open_list,Hole,Closed_list) :-
    is_of_type(var,Closed_list),
    is_of_type(partial_list,Open_list),
    is_of_type(var,Hole),
    !,
    Hole = [],
    Closed_list = Open_list,
    must_be(proper_list,Closed_list).

% Create open list and hole given closed list
open_closed_list(Open_list,Hole,Closed_list) :-
    is_of_type(proper_list,Closed_list),
    is_of_type(var,Open_list),
    is_of_type(var,Hole),
    open_closed_list_prime(Closed_list,Hole,Open_list),
    must_be(partial_list,Open_list).

open_closed_list_prime([],Hole,Hole).
open_closed_list_prime([H0|T0],Hole,[H0|T]) :-
    open_closed_list_prime(T0,Hole,T).

Test case for proceeding difference list predicates.


:- 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 ).

test(006) :-
    L1 = [32|H1],
    L2 = [32|H2],
    L3 = [32|H3],
    H1 = L2,
    H2 = L3,

    assertion( L1 == [32,32,32|H3] ),
    assertion( H1 == [32,32|H3] ),
    assertion( L2 == [32,32|H3] ),
    assertion( H2 == [32|H3] ),
    assertion( L3 == [32|H3] ),
    assertion( H3 == H3 ).

open_closed_list_test_case_generator( Hole      , Hole, []    ).
open_closed_list_test_case_generator( [a|Hole]  , Hole, [a]   ).
open_closed_list_test_case_generator( [A|Hole]  , Hole, [A]   ).
open_closed_list_test_case_generator( [a,b|Hole], Hole, [a,b] ).
open_closed_list_test_case_generator( [A,b|Hole], Hole, [A,b] ).
open_closed_list_test_case_generator( [a,B|Hole], Hole, [a,B] ).
open_closed_list_test_case_generator( [A,B|Hole], Hole, [A,B] ).

test(007,[forall(open_closed_list_test_case_generator(Open_list,Hole,Expected_close_list))]) :-
    open_closed_list(Open_list,Hole,Closed_list),

    assertion( Closed_list == Expected_close_list ),
    assertion( Hole == [] ).

test(008,[forall(open_closed_list_test_case_generator(Expected_open_list,_,Closed_list))]) :-
    open_closed_list(Open_list,_,Closed_list),

    assertion( Open_list =@= Expected_open_list ).

:- end_tests(difference_list).

Example that creates a difference list useful for adding spacing when generating pretty printed text.

Notice that code is recursive and the base case

spacing_difference_list(0,Hole,Hole)

uses a variable Hole and not []

spacing_difference_list(0,Hole,Hole) :- !.
spacing_difference_list(Length0,Spacing,Hole) :-
    must_be(nonneg,Length0),
    must_be(partial_list,Spacing),
    must_be(var,Hole),
    succ(Length,Length0),
    spacing_difference_list(Length,Spacing0,Hole),
    Spacing = [32|Spacing0].

Test cases for spacing_difference_list/3

:- begin_tests(spacing_difference_list).

test(001) :-
    spacing_difference_list(0,Spacing,Hole),

    assertion( Spacing == Hole ),
    assertion( is_of_type(var,Hole) ).

test(002) :-
    spacing_difference_list(1,Spacing,Hole),

    assertion( Spacing == [32|Hole] ),
    assertion( is_of_type(var,Hole) ).

test(003) :-
    spacing_difference_list(2,Spacing,Hole),

    assertion( Spacing == [32,32|Hole] ),
    assertion( is_of_type(var,Hole) ).

test(004) :-
    spacing_difference_list(3,Spacing,Hole),

    assertion( Spacing == [32,32,32|Hole] ),
    assertion( is_of_type(var,Hole) ).

test(005) :-
    spacing_difference_list(3,Spacing1,Hole1),
    spacing_difference_list(4,Spacing2,Hole2),

    assertion( Spacing1 == [32,32,32|Hole1] ),
    assertion( is_of_type(var,Hole1) ),

    assertion( Spacing2 == [32,32,32,32|Hole2] ),
    assertion( is_of_type(var,Hole2) ),

    Hole = Spacing1,
    Hole1 = Spacing2,
    Hole2 = [],

    assertion( Hole == [32,32,32,32,32,32,32] ).

:- end_tests(spacing_difference_list).

Here is a variation of a popular predicate string_without//2 form the DCG/basics library (source)

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) --> [].

Test cases for string_without_partial_list//3

:- 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),

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

:- end_tests(string_without).

Pretty print of XML using DCG to parse the XML and difference list to reconstruct the XML with the added whitespace.

Still working on this, but compete enough to show.

If you ever heard the expression

Using difference list is about filling the holes

and you understand the code below then the statement should make sense.


xml_pretty_print(Transformed_text) -->
    element_04(0,Hole0,Hole),
    {
        Hole = [], % Convert open list to closed list
        string_codes(Transformed_text,Hole0)
    }.

element_04(Spacing_length,Hole0,Hole) -->
    tag_begin_04(Spacing_length,Hole0,Hole1),
    optional_line_end_04,
    value_04(Spacing_length,Hole1,Hole2),
    optional_line_end_04,
    tag_end_04(Spacing_length,Hole2,Hole3),
    optional_line_end_04,
    { Hole = Hole3 }.

elements_04(Spacing_length,Hole0,Hole) -->
    { Hole0 = [10|Hole1] },
    element_04(Spacing_length,Hole1,Hole2), !,
    elements_04(Spacing_length,Hole2,Hole).
elements_04(_Spacing_length,Hole0,Hole) -->
    { 
        Hole0 = [10|Hole1] ,
        Hole = Hole1 
    }.

optional_line_end_04 -->
    (
        "\n", !
    ;
        []
    ).

% Value is a single value
value_04(_Spacing_length,Hole0,Hole) -->
    \+ "<",
    string_without_partial_list("<",Value_codes,Hole1), !,
    {
        Hole0 = Value_codes,
        Hole1 = Hole
    }.
% Value is a group of values
value_04(Spacing_length0,Hole0,Hole) -->
    { Spacing_length is Spacing_length0 + 3 },
    elements_04(Spacing_length,Hole0,Hole1),
    {
        Hole = Hole1
    }.

tag_begin_04(Spacing_length,Hole0,Hole) -->
    \+ "</",
    "<",
    string_without_partial_list(">",Tag_codes,Hole3),
    ">",
    { spacing_difference_list(Spacing_length,Spacing,Hole1) },
    {
        Hole0 = Spacing,
        Hole1 = [0'<|Hole2],
        Hole2 = Tag_codes,
        Hole3 = [0'>|Hole4],
        Hole = Hole4
    }.

tag_end_04(_Spacing_length,Hole0,Hole) -->
    "</",
    string_without_partial_list(">",Tag_codes,Hole2),
    ">",
    {
        Hole0 = [0'<,0'/|Hole1],
        Hole1 = Tag_codes,
        Hole2 = [0'>|Hole3],
        Hole3 = Hole
    }.

Test cases


:- begin_tests(xml_pretty_print).

test(001) :-
    Input = "<note>",
    string_codes(Input,Codes),
    DCG = tag_begin_04(3,Hole0,Hole),
    phrase(DCG,Codes,[]),

    assertion( Hole0 == [32,32,32,60,110,111,116,101,62|Hole] ),
    assertion( var(Hole)  ).

test(002) :-
    Input = "</note>",
    string_codes(Input,Codes),
    DCG = tag_end_04(3,Hole0,Hole),
    % nl,
    phrase(DCG,Codes,[]),

    assertion( Hole0 == [60,47,110,111,116,101,62|Hole] ),
    assertion( var(Hole)  ).

test(003) :-
    Input = "Alice",
    string_codes(Input,Codes),
    DCG = value_04(3,Hole0,Hole),
    % nl,
    phrase(DCG,Codes,[]),

    assertion( Hole0 == [65,108,105,99,101|Hole] ),
    assertion( var(Hole)  ).

test(004) :-
    Input = "<to>Bob</to>",
    string_codes(Input,Codes),
    DCG = element_04(3,Hole0,Hole),
    phrase(DCG,Codes,[]),

    assertion( Hole0 == [32,32,32,60,116,111,62,66,111,98,60,47,116,111,62|Hole] ),
    assertion( var(Hole)  ).

test(005) :-
    Input = "<to>Bob</to><from>Alice</from>",
    string_codes(Input,Codes),
    DCG = elements_04(3,Hole0,Hole),
    % nl,
    phrase(DCG,Codes,[]),

    assertion( Hole0 == [10,32,32,32,60,116,111,62,66,111,98,60,47,116,111,62,10,32,32,32,60,102,114,111,109,62,65,108,105,99,101,60,47,102,114,111,109,62,10|Hole] ),
    assertion( var(Hole)  ).

% Ref: https://www.w3schools.com/xml/note.xml
test(006) :-
    Input = "\c
        <note>\c
          <to>Bob</to>\c
          <from>Alice</from>\c
          <heading>Reminder</heading>\c
          <body>Don't forget me this weekend!</body>\c
        </note>\c
        ",
    string_codes(Input,Codes),
    DCG = xml_pretty_print(Transformed_text),
    phrase(DCG,Codes,[]),

    assertion( Transformed_text == "<note>\n   <to>Bob</to>\n   <from>Alice</from>\n   <heading>Reminder</heading>\n   <body>Don't forget me this weekend!</body>\n</note>" ).

test(007) :-
    Input = "\c
        <note>\n\c
          <to>Bob</to>\n\c
          <from>Alice</from>\n\c
          <heading>Reminder</heading>\n\c
          <body>Don't forget me this weekend!</body>\n\c
        </note>\n\c
        ",
    string_codes(Input,Codes),
    DCG = xml_pretty_print(Transformed_text),
    phrase(DCG,Codes,[]),

    assertion( Transformed_text == "<note>\n   <to>Bob</to>\n   <from>Alice</from>\n   <heading>Reminder</heading>\n   <body>Don't forget me this weekend!</body>\n</note>" ).

:- end_tests(xml_pretty_print).
4 Likes