Now that I have a better grasp on how to combine multiple streams (difference list) using EDCG here is the code. As I am not an expert with EDCG this may not be the best way, but it does work.
Click triangle to see example code
% -----------------------------------------------------------------------------
:- module(edcg_example,
[
dl_append_edcg/6
]).
% -----------------------------------------------------------------------------
:- use_module(library(edcg)).
% -----------------------------------------------------------------------------
% These are just two versions of the classic difference list append.
% These are here for use with the test cases to show that these and the EDCG
% version all pass the same test cases.
dl_append_expanded(Source_1,Hole_1,Source_2,Hole_2,Destination,Destination_hole) :-
Destination = Source_1,
Hole_1 = Source_2,
Hole_2 = Destination_hole.
dl_append(Source_1,Source_2,Source_2,Hole_2,Source_1,Hole_2).
% -----------------------------------------------------------------------------
edcg:acc_info(source_1, Destination, Source_1, _Hole_1, Destination = Source_1).
edcg:acc_info(source_2, Hole_1, Source_2, _Hole_2, Hole_1 = Source_2).
edcg:acc_info(destination, Hole_2, _Destination, Destination_hole, Hole_2 = Destination_hole).
edcg:pred_info(dl_append_edcg,0,[source_1,source_2,destination]).
% NB Originally tried using EDCG notation Destination/destination/Hole_2 which failed miserably.
dl_append_edcg -->>
Destination/destination, % Set (unify) start of difference list
[Destination]:source_1, % Set (unify) hole of difference list
Hole_1/source_1,
[Hole_1]:source_2,
Hole_2/source_2,
[Hole_2]:destination.
% ?- listing(dl_append_edcg/6).
% edcg_example:dl_append_edcg(A,
% Hole_1,
% B,
% Hole_2,
% Destination,
% C) :-
% true,
% Destination=A,
% true,
% true,
% Hole_1=B,
% true,
% true,
% Hole_2=C,
% true.
% Refined variable names by hand
%
% edcg_example:dl_append_edcg(Source_1,
% Hole_1,
% Source_2,
% Hole_2,
% Destination,
% Destination_hole) :-
% true,
% Destination=Source_1,
% true,
% true,
% Hole_1=Source_2,
% true,
% true,
% Hole_2=Destination_hole,
% true.
% Refined variable names by hand
% Removed true statements
%
% edcg_example:dl_append_edcg(Source_1,
% Hole_1,
% Source_2,
% Hole_2,
% Destination,
% Destination_hole) :-
% Destination=Source_1,
% Hole_1=Source_2,
% Hole_2=Destination_hole.
% Refined variable names by hand
% Removed true statements
% Refactored unification into head
%
% edcg_example:dl_append_edcg(Source_1, Source_2, Source_2, Hole_2, Source_1, Hole_2).
% -----------------------------------------------------------------------------
% Predicates used by test that conform to same signature.
dl_append_expanded(Source_1,Hole_1,Source_2,Hole_2,Output) :-
dl_append_expanded(Source_1,Hole_1,Source_2,Hole_2,Output,Output_hole),
Output_hole = []. % Convert open list to closed list
dl_append(Source_1,Hole_1,Source_2,Hole_2,Output) :-
dl_append(Source_1,Hole_1,Source_2,Hole_2,Output,Output_hole),
Output_hole = []. % Convert open list to closed list
dl_append_edcg(Source_1,Hole_1,Source_2,Hole_2,Output) :-
dl_append_edcg(Source_1,Hole_1,Source_2,Hole_2,Output,Output_hole),
Output_hole = []. % Convert open list to closed list
:- begin_tests(dl_append).
append_list_test_case_generator( Hole_1 , Hole_1, Hole_2 , Hole_2, [] ).
append_list_test_case_generator( [1|Hole_1], Hole_1, [a|Hole_2], Hole_2, [1,a] ).
append_list_test_case_generator( [1,2|Hole_1], Hole_1, [a,b|Hole_2], Hole_2, [1,2,a,b] ).
append_list_test_case_generator( [1,2,3|Hole_1], Hole_1, [a,b,c|Hole_2], Hole_2, [1,2,3,a,b,c] ).
append_list_test_case_generator( [1|Hole_1], Hole_1, Hole_2 , Hole_2, [1] ).
append_list_test_case_generator( Hole_1 , Hole_1, [a|Hole_2], Hole_2, [a] ).
test(01,[forall(append_list_test_case_generator(Source_1,Hole_1,Source_2,Hole_2,Output))]) :-
dl_append_expanded(Source_1,Hole_1,Source_2,Hole_2,Output).
test(02,[forall(append_list_test_case_generator(Source_1,Hole_1,Source_2,Hole_2,Output))]) :-
dl_append(Source_1,Hole_1,Source_2,Hole_2,Output).
test(03,[forall(append_list_test_case_generator(Source_1,Hole_1,Source_2,Hole_2,Output))]) :-
dl_append_edcg(Source_1,Hole_1,Source_2,Hole_2,Output).
:- end_tests(dl_append).