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. *
- * *
- ****************************************************************************/
-
- /* $call.P */
-
- $call_export([call/1,'_$interp'/2,'_$call'/1,call/2]).
-
- % $call_use : $modules
-
- '_$interp'(','(A,B),CP) :- !,'_$interp'(A,CP),'_$interp'(B,CP).
-
- '_$interp'(';'(A,B),CP) :- !,'_$interpor'(A,CP,B).
-
- '_$interp'('!',CP) :- '_$cutto'(CP).
-
- '_$interp'('->'(A,B),CP) :- !,
- '_$savecp'(NCP),'_$interp'(A,NCP),!,'_$interp'(B,CP).
-
- '_$interp'([H|L], _) :- !, $consult_list([H|L]).
- '_$interp'(Goal,_) :- '_$builtin'(10). /* '_$call'(Goal) */
-
- '_$interpor'('->'(Bool,Then),CP,Else) :-
- !,'_$interpif'(Bool,CP,Else,Then).
- '_$interpor'(A,CP,_) :- '_$interp'(A,CP).
- '_$interpor'(_,CP,B) :- '_$interp'(B,CP).
-
- '_$interpif'(Bool,CP,Else,Then) :-
- '_$savecp'(NCP),'_$interp'(Bool,NCP),!,'_$interp'(Then,CP).
- '_$interpif'(_,CP,Else,_) :- '_$interp'(Else,CP).
-
-
- '_$call'([H|L]) :- !, $consult_list([H|L]).
- '_$call'(X) :- '_$builtin'(10).
-
- (A,B) :- '_$call'(A),'_$call'(B).
-
- ','(A,B,C,D) :- '_$call'(A),'_$call'(B),'_$call'(C),'_$call'(D).
-
- /*
- (A->B;C) :- !,(call(A) -> '_$call'(B) ; '_$call'(C)).
- (A;B) :- '_$call'(A).
- (A;B) :- '_$call'(B).
- */
-
- ';'(A, B) :-
- A = (Test -> Then) ->
- (call(Test) -> '_$call'(Then) ; '_$call'(B)) ;
- ('_$call'(A) ; '_$call'(B)).
-
-
- (A->B) :- call(A) -> '_$call'(B).
-
- not(A) :- call(A) -> fail ; true.
-
- '\+'(A) :- call(A) -> fail ; true.
-
- % call/1 is unaffected by the modules system.
-
- call(X) :- '_$savecp'(C),'_$interp'(X,C).
-
- % call/2 used to call predicates in remote structures. The call to
- % $expand_body/2 ensures that predicates like name/2 are converted into
- % their correct form name/3, etc. The call to $move_clause/4 physically
- % alters the tags within the call to the destination structure tag. Note
- % that the call itself can only contain references to one structure only (ie.
- % it cannot refer to any substructures from the current structure).
-
- call(X,Str) :-
- ( $isa_structuretag(Str) ->
- ( Str == perv -> call(X) ;
- ( $call_oldtag(X,Oldtag),
- $expand_body(X,X0,Str),
- $move_clause(X0,Oldtag,Str,Y),
- call(Y) ) ) ;
- ( $telling(Tell), $tell(user),
- $writename('*** Error : Second arg to call/2 must be structure tag'),
- $nl, $tell(Tell), fail ) ).
-
- % $call_oldtag/2 grabs the tag at the head of the call (or tag of the first
- % call if there are several), and all other tags in the call have to be
- % equal to this one.
-
- $call_oldtag((X, _), Tag) :- !,
- $call_oldtag(X, Tag).
- $call_oldtag((X; _), Tag) :- !,
- $call_oldtag(X, Tag).
- $call_oldtag((X -> _), Tag) :- 1,
- $call_oldtag(X, Tag).
- $call_oldtag(X, Tag) :-
- $functor0(X, Name),
- $dismantle_name(Name, _, Tag).
-