1/***************************************************************************** 2 * This file is part of the Prolog Development Tool (PDT) 3 * 4 * Author: G�nter Kniesel (among others) 5 * WWW: http://sewiki.iai.uni-bonn.de/research/pdt/start 6 * Mail: pdt@lists.iai.uni-bonn.de 7 * Copyright (C): 2004-2012, CS Dept. III, University of Bonn 8 * 9 * All rights reserved. This program is made available under the terms 10 * of the Eclipse Public License v1.0 which accompanies this distribution, 11 * and is available at http://www.eclipse.org/legal/epl-v10.html 12 * 13 ****************************************************************************/ 14 15% Date: 21.11.2005 16 17:- if(pdt_support:pdt_support(remove_duplicates)). 18:- module( ctc_lists, [ 19 nth1_non_unifying/3, % (Index, +List, Elem) ?+? is nondet, ??? is infinite 20 union_and_intersection/4, % (+Set1,+Set2,?Union,?Intersection)! <- identity-based equality 21 ctc_intersection/3, % (+Set1,+Set2, ?Intersection)! <- unification-based equality 22 union_sorted/3, % (+Set1,+Set2,?Union)! 23 union_order_preserving/3, % (+Set1,+Set2,?Union)! 24 remove_duplicates_sorted/2,% (+List,?DuplicateFree)! 25 list_sum/2, % (+Numbers,?Total)! 26 traverseList/3, % (+List,+Stop,+Pred) is nondet 27 list_to_disjunction/2, % (+List,?Disjunction) is det. 28 list_to_conjunction/2, % (+List,?Conjunction) is det. 29 pretty_print_list/1, % (+List)!io 30 pretty_print_list/2, % (+List,+Indent)!io 31 list_2_comma_separated_list/2, % (+List,-Atom) is det. 32 list_2_separated_list/3 % (+List,-Atom) is det. 33] ). 34:- else. 35:- module( ctc_lists, [ 36 nth1_non_unifying/3, % (Index, +List, Elem) ?+? is nondet, ??? is infinite 37 union_and_intersection/4, % (+Set1,+Set2,?Union,?Intersection)! <- identity-based equality 38 ctc_intersection/3, % (+Set1,+Set2, ?Intersection)! <- unification-based equality 39 union_sorted/3, % (+Set1,+Set2,?Union)! 40 union_order_preserving/3, % (+Set1,+Set2,?Union)! 41 remove_duplicates_sorted/2,% (+List,?DuplicateFree)! 42 remove_duplicates/2, % (+List,?DuplicateFree)! 43 list_sum/2, % (+Numbers,?Total)! 44 traverseList/3, % (+List,+Stop,+Pred) is nondet 45 list_to_disjunction/2, % (+List,?Disjunction) is det. 46 list_to_conjunction/2, % (+List,?Conjunction) is det. 47 pretty_print_list/1, % (+List)!io 48 pretty_print_list/2, % (+List,+Indent)!io 49 list_2_comma_separated_list/2, % (+List,-Atom) is det. 50 list_2_separated_list/3, % (+List,-Atom) is det. 51 finite_length/2 52] ). 53:- endif. 54 55:- use_module(library(lists)). 56:- use_module(pdt_support, [pdt_support/1]).
64nth1_non_unifying(Index, List, Elem) :- 65 nth1_non_unifying__(List, Elem, Index, 1). 66 67nth1_non_unifying__([H|_], Elem, Index, Depth) :- 68 Elem == H, 69 Index = Depth. 70nth1_non_unifying__([_|T], Elem, Index, Depth) :- 71 Deeper is Depth+1, 72 nth1_non_unifying__(T, Elem, Index, Deeper).
85union_and_intersection(S1,S2,U,I) :- 86 length(S1,L1), 87 length(S2,L2), 88 ( L1 < L2 89 -> union_inters__(S1,S2,U,I) % start with shorter list 90 ; union_inters__(S2,S1,U,I) % start with shorter list 91 ). 92 93union_inters__([],Set2,Set2,[]). 94union_inters__(Set1,[],Set1,[]) :- 95 Set1 \= []. 96union_inters__([X|T1],[Y|T2],NewU, NewI):- 97 ( (X==Y, union_inters__(T1,T2,U,I), NewU=[X|U], NewI=[X|I]) 98 ; (X@<Y, union_inters__(T1,[Y|T2],U,I), NewU=[X|U], NewI=I ) 99 ; (X@>Y, union_inters__([X|T1],T2,U,I), NewU=[Y|U], NewI=I ) 100 ). 101 102 103ctc_intersection(S1,S2,I) :- 104 % prevent propagating side-effects of unification to the call site 105 copy_term(S2,S2C), 106 % start with shorter list (for better performance) 107 length(S1,L1), 108 length(S2,L2), 109 ( L1 < L2 110 -> inters__unification_based(S1,S2C,I) 111 ; inters__unification_based(S2C,S1,I) 112 ). 113 114% Caution: This version unifies terms when compring them. 115% If this is not desired, the call site is responsible to 116% pass copies of the relevant terms. 117inters__unification_based([],_,[]). 118inters__unification_based(Set1,[],[]) :- 119 Set1 \= []. 120inters__unification_based([X|T1],[Y|T2], NewI):- 121 ( (X=Y, !, inters__unification_based(T1, T2,I), NewI=[X|I]) 122 ; (X@<Y,!, inters__unification_based(T1,[Y|T2],I), NewI=I ) 123 ; (X@>Y, inters__unification_based([X|T1],T2,I), NewI=I ) 124 ). 125 126inters__identity_based([],_,[]). 127inters__identity_based(Set1,[],[]) :- 128 Set1 \= []. 129inters__identity_based([X|T1],[Y|T2], NewI):- 130 ( (X==Y, inters__identity_based(T1, T2,I), NewI=[X|I]) 131 ; (X@<Y, inters__identity_based(T1,[Y|T2],I), NewI=I ) 132 ; (X@>Y, inters__identity_based([X|T1],T2,I), NewI=I ) 133 ). 134 135% Test: 136% 137% try_uai(C,F,G,H) :- 138% C = [_G548, _G554, _G556, _G557, _G558, _G559] , 139% F = [_G564, _G556, _G570, _G571, _G572], 140% union_inters__(C,F,G,H).
151union_sorted(Set1,Set2,Set12):- 152 once(union_sorted__(Set1,Set2,Set12)). 153 154union_sorted__([],Set2,Set2). 155union_sorted__(Set1,[],Set1) :- 156 Set1 \= []. 157union_sorted__([X|T1],[Y|T2],NewU):- 158 ( (X==Y, union_sorted__(T1,T2,U), NewU=[X|U]) 159 ; (X@<Y, union_sorted__(T1,[Y|T2],U), NewU=[X|U]) 160 ; (X@>Y, union_sorted__([X|T1],T2,U), NewU=[Y|U]) 161 ).
173union_order_preserving(S1,S2,Res) :- 174 append(S1,S2,S3), 175 list_to_set(S3,Res), !. 176 177/* 178remove_duplicates([First|Rest],NoDup) :- 179 member(First,Rest), 180 !, 181 remove_duplicates(Rest,NoDup). 182remove_duplicates([First|Rest],[First|NoDup]) :- 183 remove_duplicates(Rest,NoDup). 184remove_duplicates([],[]). 185*/
199remove_duplicates_sorted([], []) . 200remove_duplicates_sorted([First|Rest], [First|UniqueRest]) :- 201 remove_duplicates_sorted__(Rest, First, UniqueRest). 202 203remove_duplicates_sorted__([],_,[]). 204remove_duplicates_sorted__([First|Rest], Previous, Result ) :- 205 ( First = Previous 206 -> ( Result = RestNoDup, 207 remove_duplicates_sorted__(Rest, Previous, RestNoDup) 208 ) 209 ; ( Result = [First|RestNoDup], 210 remove_duplicates_sorted__(Rest, First, RestNoDup) 211 ) 212 ). 213 214 215:- if(\+ pdt_support:pdt_support(remove_duplicates)).
221remove_duplicates([First|Rest],[First|NoDup]) :- 222 split_unique(Rest,First,Before,After), 223 !, 224 append(Before,After,BA), 225 remove_duplicates(BA,NoDup). 226remove_duplicates([First|Rest],[First|NoDup]) :- 227 remove_duplicates(Rest,NoDup). 228remove_duplicates([],[]). 229:- endif.
237split_unique([E|T],E,[],TwithoutE) :- 238 remove_duplicates([E|T],[E|TwithoutE]). 239split_unique([H|T],E,[H|Before],After) :- 240 split_unique(T,E,Before,After). 241 242 243/* 244flatten_one_level([],[]) . 245flatten_one_level([H|T],Res) :- 246 flatten_one_level(T,Flat), 247 append(H,Flat,Res). 248*/
Sum up a list of numbers.
257list_sum(Numbers,Total) :- list_sum(Numbers,0,Total). 258list_sum([],X,X). 259list_sum([H|T],Temp,Res) :- 260 NewTemp is Temp+H, 261 list_sum(T,NewTemp,Res). 262 263%list_sum([],0). 264%list_sum([1],1). 265%list_sum([1,2],3). 266%list_sum([1,2,3,4,0,3,2,1],16).
274 % 275traverseList(List,Stop,_Pred):- 276 List == Stop, 277 !. 278traverseList(List,Stop,Pred):- 279 List =.. [_F,Head,Tail], 280 Pred =.. [_P,Head], 281 call(Pred), 282 traverseList(Tail,Stop,Pred).
288list_to_disjunction([ ],true) :-!. 289list_to_disjunction([A],A ) :-!. 290list_to_disjunction([A|B],(A;Disj)) :- 291 list_to_disjunction(B,Disj).
297list_to_conjunction([ ],true) :-!. 298list_to_conjunction([A],A ) :-!. 299list_to_conjunction([A|B],(A,Conj)) :- 300 list_to_conjunction(B,Conj).
310pretty_print_list(List) :-
311 pretty_print_list(List, 2) .
322pretty_print_list(List, Indent) :- pp_list(List, 0, Indent, ' '). 323 324 325pp_list([], Current, _, Komma) :- 326 write_line_indented(Current,[], Komma ). 327 328pp_list([A|B], Current, Indent, Komma) :- 329 write_line_indented(Current,'[', ' '), 330 Next is Current + Indent, 331 pp_list_body([A|B], Next, Indent), 332 write_line_indented(Current,']',Komma). 333 334 335pp_list_body([A ], Current, Indent) :- !, 336 pp_list_element(A,Current,Indent,' ') . 337pp_list_body([A|B], Current, Indent) :- pp_list_element(A,Current,Indent,','), 338 pp_list_body(B, Current, Indent). 339 340pp_list_element(A,Current,Indent,X) :- 341 ( is_list(A) 342 -> pp_list(A,Current,Indent, X) 343 ; write_line_indented(Current, A, X) 344 ) .
352write_line_indented(Indent,What,Separator) :- 353 atomic_list_concat(['~t~',Indent,'|~w~a~n'],Formatstring), 354 format(Formatstring,[What,Separator]). 355 356 357 358 359list_2_comma_separated_list([],'') :- !. 360list_2_comma_separated_list([Element],Element) :- !. 361list_2_comma_separated_list([Element|[H|T]],ElementComma) :- 362 list_2_comma_separated_list([H|T],RestAtom), 363 aformat(ElementComma,'~w,~w',[Element,RestAtom]). 364 365list_2_separated_list([],_,'') :- !. 366list_2_separated_list([Element],_,Element) :- !. 367list_2_separated_list([Element|Rest],Separator,ElementSeparated) :- 368 list_2_separated_list(Rest,Separator,RestAtom), 369 format(atom(ElementSeparated),'~w~w~w',[Element,Separator,RestAtom]). 370 371 372aformat(Atom,FormatString,List):- 373 format(atom(Atom),FormatString,List). 374 375test_PPL :- pretty_print_list([1,2,3,a,b,c,X,Y,Z,f(a),g(b,c),h(X,Y,Z)]) . 376test_PPL :- pretty_print_list([1,2,3,a,b,c,X,Y,Z,f(a),g(b,c),h(X,Y,Z)], 8) . 377 378finite_length(List, Length) :- 379 '$skip_list'(Length, List, Tail), 380 Tail == []