1/* AUTHOR(S) ************************************************************
    2
    3Michel Wermelinger
    4Dept. de Informatica, Univ. Nova de Lisboa, Quinta da Torre
    5P - 2825 Monte da Caparica, PORTUGAL
    6Phone: (+351) (1) 295 44 64 ext. 1360  Internet: mw@fct.unl.pt
    7
    8************************************************************************/
    9
   10/* GENERALITIES *********************************************************
   11 
   12File Name	: LIST.PL
   13Creation Date	: 90/06/16 	By: mw
   14Abbreviations	: mw - Michel Wermelinger 
   15Description	: Utility predicates on lists and sets (lists without
   16		  duplicates; the order of the elements doesn't matter)
   17 
   18************************************************************************/
   19
   20/* HISTORY **************************************************************
   21
   221.01	92/03/20  mw	added nth_delete
   23
   24************************************************************************/
   25
   26/* CONTENTS *************************************************************
   27 
   28conc/3		concatenates two lists 
   29delete_all/3	deletes from a list all occurrences of a given element 
   30delete_dup/2	deletes all duplicate occurrences of every list member
   31delete_eq/2	the same as delete_dup/2 but uses == instead of =
   32delete_one/3	deletes from a list a single occurrence of a given element
   33is_list/1       succeeds iff argument is a list
   34last/2		computes the last element of a list 
   35length/2	computes the number of elements of a list
   36list_of/2	succeeds if all elements are equal
   37member/2	tests for list membership 
   38nth_delete/3    deletes nth member of a list
   39nth_member/3	permits the use of a list as an array
   40reverse/2	reverses the order of the list elements
   41
   42difference/3	computes the difference of two sets
   43intersection/3	computes the common members of two sets
   44subset/2	tests if the members of a list are contained in another one
   45union/3		computes the union of two sets
   46
   47apply/2		applies a given predicate to every list element
   48map/3		applies a given predicate to map a list into another one 
   49
   50************************************************************************/
   51
   52/************************************************************************
   53
   54			L I S T   P R E D I C A T E S
   55
   56************************************************************************/
   57
   58/* conc/3 ***************************************************************
   59
   60Usage		: conc(?List1, ?List2, ?List3)
   61Argument(s)	: lists
   62Description	: succeeds iff List3 is the concatenation of List1 and List2
   63Notes		: at least two of the three arguments must be given 
   64
   65************************************************************************/
   66
   67conc([H|T], L, [H|R]) :- 
   68	conc(T, L, R).
   69conc([], L, L).
   70
   71/* delete_all/3 *********************************************************
   72
   73Usage		: delete_all(+Element, +List, ?NewList)
   74Argument(s)	: term and lists
   75Description	: NewList is List but with no occurrences of Element
   76Notes		: 
   77
   78************************************************************************/
   79
   80delete_all(H, [H|T], T2) :-
   81	delete_all(H, T, T2).
   82delete_all(X, [H|T], [H|T2]) :-
   83	delete_all(X, T, T2).
   84delete_all(_, [], []) :-
   85	!.
   86
   87/* delete_dup/2 *********************************************************
   88
   89Usage		: delete_dup(+List, ?NewList)
   90Argument(s)	: lists
   91Description	: NewList has the same members as List but without duplicates
   92Notes		: 
   93
   94************************************************************************/
   95
   96delete_dup([H|T1], [H|T3]) :-
   97	delete_all(H, T1, T2),
   98	delete_dup(T2, T3).
   99delete_dup([], []).
  100
  101/* delete_eq/2 **********************************************************
  102
  103Usage		: delete_eq(+List, ?NewList)
  104Argument(s)	: lists
  105Description	: the same as delete_dup/2 but two elements are duplicates
  106		  iff they are equal, not if they just unify 
  107Notes		: 
  108
  109************************************************************************/
  110
  111delete_eq([H|T], L) :-
  112	member(X, T), X == H, delete_eq(T, L).
  113delete_eq([H|T], [H|L]) :-
  114	delete_eq(T, L).
  115delete_eq([], []) :-
  116	!.
  117
  118/* delete_one/2 *********************************************************
  119
  120Usage		: delete_one(+Element, +List, ?NewList)
  121Argument(s)	: 		term	list	list
  122Description	: deletes one single occurrence of Element from List
  123		  returning NewList 
  124Notes		: succeeds always, even if Element is not member of List
  125
  126************************************************************************/
  127
  128delete_one(H, [H|T], T).
  129delete_one(H, [X|T], [X|R]) :-
  130	delete_one(H, T, R).
  131delete_one(_, [], []).
  132
  133/* is_list/1 ************************************************************
  134
  135Usage		: is_list(+List)
  136Argument(s)	: term
  137Description	: succeeds iff List is a valid Prolog list
  138Notes		: 
  139
  140************************************************************************/
  141
  142%is_list([]).
  143%is_list([_|_]).
  144
  145/* last/2 ***************************************************************
  146
  147Usage		: last(+List, ?Element)
  148Argument(s)	: 	list	term
  149Description	: succeeds iff Element is the last element of List
  150Notes		: 
  151
  152************************************************************************/
  153:- if( \+ current_predicate(last/1)).  154
  155last(L, X) :-
  156	conc(_, [X], L).
  157
  158:- endif.  159
  160/* length/2 *************************************************************
  161
  162Usage		: length(+List, ?Length)
  163Argument(s)	: 	  list	integer
  164Description	: succeeds iff Length is the number of elements of List
  165Notes		: 
  166
  167************************************************************************/
  168:- if( \+ current_predicate(length/2)).  169
  170length([_|T], Y) :-
  171	length(T, X), succ(X, Y).
  172length([], 0).
  173
  174:- endif.  175
  176/* list_of/2 ************************************************************
  177
  178Usage		: list_of(?List, ?Element)
  179Argument(s)	: 	   list	   term
  180Description	: succeeds iff all members of List unify with Element
  181Notes		: at least one of the arguments must be instantiated
  182
  183************************************************************************/
  184
  185list_of([], _).
  186list_of([H|T], H) :- list_of(T, H).
  187
  188/* member/2 *************************************************************
  189
  190Usage		: member(?Element, +List)
  191Argument(s)	: 	   term	    list
  192Description	: succeeds iff Element unifies with a member of List
  193Notes		: if -Element, generates all list members by backtracking 
  194
  195************************************************************************/
  196/*
  197member(H, [H|_]).
  198member(H, [_|T]) :-
  199	member(H, T).
  200
  201*/
  202
  203/* nth_member/2 *********************************************************
  204
  205Usage		: nth_member(?Element, ?List, ?N)
  206Argument(s)	: 	       term	list  integer
  207Description	: succeeds iff the N-th member of List is Element
  208Notes		: at least two of the predicates must be instantiated
  209		  the first element of List has position 1, not 0
  210
  211************************************************************************/
  212
  213nth_member(H, [H|_], 1).
  214nth_member(H, [_|T], N) :-
  215	nth_member(H, T, N0), succ(N0, N).
  216
  217/* nth_delete/3 *********************************************************
  218
  219Usage		: nth_delete(+List1, +Number, ?List2)
  220Argument(s)	: 	      list   integer  list
  221Description	: succeeds iff List2 is List1 without its N-th member
  222Notes		: 
  223
  224************************************************************************/
  225
  226nth_delete([_|T], 1, T).
  227nth_delete([_|T], N, R) :-
  228	N0 is N - 1, nth_delete(T, N0, R).
  229
  230/* reverse/2 ************************************************************
  231
  232Usage		: reverse(+List, ?ReversedList)
  233Argument(s)	: lists
  234Description	: succeeds iff ReversedList and List have the same members
  235		  but in opposite order
  236Notes		: 
  237
  238************************************************************************/
  239
  240reverse(List, Rev) :-
  241   	rev(List, [], Rev).
  242
  243rev([H|T], WorkList, Rev) :-
  244   	rev(T, [H|WorkList], Rev).
  245rev([], Rev, Rev).
  246
  247/************************************************************************
  248
  249			  S E T   P R E D I C A T E S
  250
  251************************************************************************/
  252
  253/* difference/3 *********************************************************
  254
  255Usage		: difference(+Set1, +Set2, ?Diff)
  256Argument(s)	: lists
  257Description	: Diff contains all members of Set1 which aren't in Set2
  258Notes		: 
  259
  260************************************************************************/
  261
  262difference([H|T], L, D) :- 
  263	member(H, L), difference(T, L, D).
  264difference([H|T], L, [H|R]) :- 
  265	difference(T, L, R).
  266difference([], _, []).
  267
  268/* intersection/3 *******************************************************
  269
  270Usage		: intersection(+Set1, +Set2, ?Intersection)
  271Argument(s)	: lists
  272Description	: Intersection contains the common members of Set1 and Set2
  273Notes		: 
  274
  275************************************************************************/
  276
  277intersection([H|L1], L2, L3) :-
  278	member(H, L2), !, 
  279	intersection(L1, L2, L4), L3 = [H|L4].
  280intersection([_|L1], L2, L3) :-
  281	intersection(L1, L2, L3).
  282intersection([], _, []).
  283
  284/* subset/2 *************************************************************
  285
  286Usage		: subset(+SubSet, +Set)
  287Argument(s)	: lists
  288Description	: succeeds iff all members of Subset are members of Set
  289Notes		: 
  290
  291************************************************************************/
  292
  293subset([H|T], S) :- 
  294	member(H, S),
  295	subset(T, S).
  296subset([], _).
  297
  298/* union/3 **************************************************************
  299
  300Usage		: union(+Set1, +Set2, ?Union)
  301Argument(s)	: sets (lists)
  302Description	: Union has all members of Set1 and Set2 but without
  303		  duplicates 
  304Notes		: 
  305
  306************************************************************************/
  307
  308union([H|X], Y, Z) :- 
  309	member(H, Y), union(X, Y, Z).
  310union([H|X], Y, [H|Z]) :- 
  311	union(X, Y, Z).
  312union([], L, L).
  313
  314/************************************************************************
  315
  316			  M E T A - P R E D I C A T E S
  317
  318************************************************************************/
  319
  320/* apply/2 **************************************************************
  321
  322Usage		: apply(+Predicate, +List)
  323Argument(s)	: 	  atom	     list
  324Description	: succeeds iff Predicate can be applied successfully to 
  325		  all members of List
  326Notes		: Predicate(+Term, ...) must exist
  327
  328************************************************************************/
  329
  330apply(P, [H|T]) :-
  331	P =.. [F, _|A], G =.. [F, H|A], call(G), apply(P, T).
  332apply(_, []).
  333	
  334/* map/2 ****************************************************************
  335
  336Usage		: map(+Predicate, +List, ?NewList)
  337Argument(s)	: atom and lists
  338Description	: NewList is obtained by applying Predicate to all
  339		  members of List
  340Notes		: Predicate(+Term1, ?Term2, ...) must exist
  341
  342************************************************************************/
  343
  344map(P, [X|L1], [Y|L2]) :- 
  345	P =.. [F, _, Arg2|T], copy_term(Arg2, Y), G =.. [F, X, Y|T],
  346        call(G), map(P, L1, L2).
  347map(_, [], [])