home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Power-Programmierung
/
CD1.mdf
/
prolog
/
library
/
diverses
/
preds.pro
< prev
next >
Wrap
Text File
|
1991-08-03
|
5KB
|
199 lines
/*
THESE ARE SOME USEFUL PROLOG PREDICATES FOR MANIPULATING LISTS AND A
REAL ARITHMETIC FUNCTION OMITTED FROM TPROLOG. THE LIST DOMAIN AND PREDICATE
DECLARATIONS ONLY ASSUME YOU'RE MANIPULATING SYMBOLS AND LISTS OF SYMBOLS.
ADDITIONAL DOMAIN AND PREDICATE DECLARATIONS CAN MAKE THESE PREDICATES
HANDLE OTHER DATA TYPES.
COMPILED BY JOHN REECE FROM C&M AND B&H
*/
domains
list = symbol*
predicates
true /* Standard Prolog predicate omitted from Turbo Prolog */
repeat /* Standard Prolog predicate omitted from Turbo Prolog */
raise(real,real,real) /* Raise a base to a real, positive or negative exponent */
append(list,list,list) /* Append two lists into the third */
member(symbol,list) /* Is symbol a member of the list? */
/* Most of these need member() or append() */
nth(symbol,integer,list) /* Remove the nth symbol from the list */
last(symbol,list) /* Get the last symbol in the list */
remove(symbol,list,list) /* Remove all occurrences of symbol from the list */
length(list,integer) /* Number of elements in the list */
flen(list,integer,integer) /* Subroutine for length() */
permute(list,list) /* Returns all the possible rearrangements of a list */
reverse(list,list) /* Reverse a list */
reverse1(list,list,list) /* Subroutine for reverse() */
efface(symbol,list,list) /* Remove the first occurence of symbol from a list*/
subst(symbol,list,symbol,list) /* Replace all occurrences of the first symbol in the first list with the second symbol */
subset(list,list) /* Is the first list a subset of the second? */
intersection(list,list,list) /* Intersection of two lists */
union(list,list,list) /* Union of two lists */
quicksort(list,list) /* Quick sort a list of symbols */
split(symbol,list,list,list) /* Subroutine for quicksort() */
clauses
/*
TRUE PREDICATE FROM STANDARD PROLOG
*/
true if
not(not(fail)).
/*
REPEAT PREDICATE FROM STANDARD PROLOG
*/
repeat.
repeat if repeat.
/*
RAISE A BASE TO A REAL, POSITIVE OR NEGATIVE EXPONENT, RETURNING RESULT.
*/
raise(_,Power,Result) if
Power = 0 and
Result = 1.0.
raise(Base,Power,Result) if
Power < 0 and
Term1 = 0.0 - Power and
raise(Base,Term1,TempResult) and
Result = 1/TempResult.
raise(Base,Power,Result) if
Power > 0 and
Result = exp(Power * ln(Base)).
/*
CONCATENATE TWO LISTS INTO LIST Y.
*/
append([],L,L).
append([X|L1],L2,[X|L3]) if
append(L1,L2,L3).
/*
IS X A MEMBER OF THE LIST?
*/
member(X, [X|_]).
member(X, [_|Y]) if member(X, Y).
/*
FIND THE nTH MEMBER OF A LIST
*/
nth(X, 1, [X|_]).
nth(X, N, [_|L]) if R = N-1,
nth(X, R, L).
/*
FIND THE LAST ELEMENT X IN A LIST.
*/
last(X,[X]).
last(X,[_|L]) if last(X,L).
/*
REMOVE THE GIVEN ITEM X FROM THE LIST, RETURNING L.
*/
remove(X,[X|T],L) if
remove(X,T,L),
!.
remove(X,[X|T],T).
remove(X,[H|T],[H|L]) if
remove(X,T,L).
/*
FIND THE LENGTH OF A LIST
*/
length(X,J) if
flen(X,J,0).
flen([],Y,Y).
flen([_|T],Y,Z) if
P = Z + 1,
flen(T, Y, P).
/*
RETURN ALL PERMUTATIONS OF LIST
*/
permute([],[]).
permute(L,[H|T]) if
append(V,[H|U],L) and
append(V,U,W) and
permute(W,T).
/*
REVERSE A LIST
*/
reverse(L1,L2) if
reverse1(L1,[],L2).
reverse1([X|L],L2,L3) if
reverse1(L,[X|L2],L3).
reverse1([],L,L).
/*
EFFACE(X,Y,Z) REMOVES THE FIRST OCCURENCE OF ELEMENT X FROM LIST Z
*/
efface(A,[A|L],L) if !.
efface(A,[B|L],[B|M]) if
efface(A,L,M).
/*
SUBST(X,L,A,M) CONSTRUCTS NEW LIST M FROM LIST L REPLACING ALL ELEMENTS
X WITH ELEMENT A
*/
subst(_,[],_,[]).
subst(X,[X|L],A,[A|M]) if
! and
subst(X,L,A,M).
subst(X,[Y|L],A,[Y|M]) if
subst(X,L,A,M).
/*
IS THE FIRST PARAMETER A SUBSET OF THE SECOND?
*/
subset([A|X],Y) if
member(A,Y) and
subset(X,Y).
subset([],_).
/*
INTERSECTION(X,Y,Z) SUCCEEDS IF THE INTERSECTION OF X AND Y IS Z
*/
intersection([],_,[]).
intersection([X|R],Y,[X|Z]) if
member(X,Y) and
! and
intersection(R,Y,Z).
intersection([_|R],Y,Z) if
intersection(R,Y,Z).
/*
UNION(X,Y,Z) SUCCEEDS IF THE UNION OF X AND Y IS Z
*/
union([],X,X).
union([X|R],Y,Z) if
member(X,Y) and
! and
union(R,Y,Z).
union([X|R],Y,[X|Z]) if
union(R,Y,Z).
/*
SORT A LIST OF SYMBOLS
*/
quicksort([],[]).
quicksort([H|T],S) if
split(H,T,A,B) and
quicksort(A,A1) and
quicksort(B,B1) and
append(A1,[H|B1],S).
split(H,[A|X],[A|Y],Z) if A <= H and split(H,X,Y,Z).
split(H,[A|X],Y,[A|Z]) if A > H and split(H,X,Y,Z).
split(_,[],[],[]).