home *** CD-ROM | disk | FTP | other *** search
- /************************************************************************
- * *
- * The SB-Prolog System *
- * Copyright SUNY at Stony Brook, 1986; University of Arizona, 1987 *
- * *
- ************************************************************************/
-
- /*-----------------------------------------------------------------
- SB-Prolog is distributed in the hope that it will be useful,
- but WITHOUT ANY WARRANTY. No author or distributor
- accepts responsibility to anyone for the consequences of using it
- or for whether it serves any particular purpose or works at all,
- unless he says so in writing. Refer to the SB-Prolog General Public
- License for full details.
-
- Everyone is granted permission to copy, modify and redistribute
- SB-Prolog, but only under the conditions described in the
- SB-Prolog General Public License. A copy of this license is
- supposed to have been given to you along with SB-Prolog so you
- can know your rights and responsibilities. It should be in a
- file named COPYING. Among other things, the copyright notice
- and this notice must be preserved on all copies.
- ------------------------------------------------------------------ */
-
- /****************************************************************************
- * *
- * This file has been changed by to include Modules Extensions *
- * Changes by : Brian Paxton 1991/92 *
- * Last update : June 1992 *
- * *
- * Organisation : University of Edinburgh. *
- * For : Departments of Computer Science and Artificial Intelligence *
- * Fourth Year Project. *
- * *
- ****************************************************************************/
-
- /* $meta.P */
-
- $meta_export([$functor/3,$univ/2,$length/2,$univ/3,$functor/4]).
-
- % $meta_use : $bmeta
-
- % $univ/3 now ensures that functions involved in 'fun X = Y' declarations
- % are processed properly.
- % At the user level, this is called =../2.
-
- $univ(X,Y) :-
- $univ(X,Y,perv).
-
- $univ(X, [X], Tag) :-
- $atomic(X), !,
- $isa_structuretag(Tag).
- $univ(X, [H|T], Tag) :-
- $atom(H), nonvar(X), !,
- $length(T, N), N > 0,
- $bldstr(H, N, Y, Tag), $arglist(Y, T, N, N),
- X = Y.
- $univ(X, [H|T], Tag) :-
- $atom(H), !,
- $length(T, N), N > 0,
- $bldstr(H, N, X, Tag), $arglist(X, T, N, N).
- $univ(X, [H|T], Tag) :-
- nonvar(X), $functor(X, H, N, Tag), $arglist(X, T, N, N).
-
- $arglist(X, [], 0, N) :- !.
- $arglist(X, [Y|Z], I, N) :- K is I - 1,
- J is N - K,
- arg(J, X, Y),
- $arglist(X, Z, K, N).
-
- $length(L,N) :- nonvar(L),$length(L,0,N).
-
- $length([],N,N).
- $length([_|L],M,N) :- M1 is M+1, $length(L,M1,N).
-
- % The original version of $functor/3 is included here for system use.
- % Has no equivalent at the user level.
-
- $functor(T, F, 0) :- $atomic(T), !, T=F.
- $functor(T, F, 0) :- $number(F), !, T=F.
- $functor(T, F, N) :- nonvar(T), !, $functor0(T, F), $arity(T, N).
- $functor(T, F, N) :- $bldstr(F, N, T).
-
- $functor(T, F, 0, Tag) :-
- $atomic(T), !,
- $isa_structuretag(Tag),
- T=F.
- $functor(T, F, 0, Tag) :-
- $number(F), !,
- $isa_structuretag(Tag),
- T=F.
- $functor(T, F, N, Tag) :-
- nonvar(T), !,
- $functor0(T, F, Tag),
- $arity(T, N).
- $functor(T, F, N, Tag) :-
- $bldstr(F, N, T, Tag).
-
-