/* Prolog-VAX v3.0 */ /* Initializing special symbols */ $rule ':-' 2 $question '?-' 1 $postfix yf 0 $prefix fy 0 $infix_la yfx 0 $infix_ra xfy 0 $infix1 xfx 0 $postfix1 xf 0 $prefix1 fx 0 $plus '+' 1 $minus '-' 1 $add '+' 2 $subtract '-' 2 $divide '/' 2 $divide div 2 $multiply '*' 2 $modulo mod 2 $exp '**' 2 $grammar '-->' 1 $grammar '-->' 2 $and ',' 2 $gcd gcd 2 $lcm lcm 2 $user user 0 $varname $var 1 $eof end_of_file 0 $eoln end_of_line 0 $compile compile 1 $link link 0 /* Initializing build-in predicates */ $abolish abolish 2 $abort abort 0 $arg arg 3 $asserta asserta 1 $assertz assertz 1 $assertz assert 1 $atom atom 1 $atomic atomic 1 $bagof bagof 3 $break break 0 $call call 1 $check check 0 $chr chr 2 $clause clause 2 $consult0 consult 0 $consult1 consult 1 $clock clock 1 $cut '!' 0 $dcl0 dcl 0 $dcl1 dcl 1 $debuggin debugging 0 $display display 1 $erase erase 1 $exit exit 0 $fail fail 0 $flush flush 0 $functor functor 3 $get get 1 $get0 get0 1 $help0 help 0 $help1 help 1 $if -> 2 $instance instance 2 $integer integer 1 $is is 2 $length length 2 $listing0 listing 0 $listing1 listing 1 $llii 'PRO$llii' 2 $load0 load 0 $load1 load 1 $name name 2 $nl nl 0 $nocheck nocheck 0 $nonvar nonvar 1 $nospy0 nospy 0 $nospy0 notrace 0 $nospy0 nodebug 0 $nospy2 nospy 2 $not not 1 $not \+ 1 $numberva numbervars 3 $op op 3 $or ; 2 $phrase phrase 2 $public0 public 0 $public2 public 2 $put put 1 $read read 1 $reconsu0 reconsult 0 $reconsu1 reconsult 1 $recorda recorda 3 $recorded recorded 3 $recordz recordz 3 $repeat repeat 0 $retract retract 1 $save0 save 0 $save1 save 1 $see see 1 $seeing seeing 1 $seen seen 0 $setof setof 3 $skip skip 1 $sort sort 2 $spy0 spy 0 $spy0 trace 0 $spy2 spy 2 $system system 1 $tab0 tab 0 $tab1 tab 1 $tell tell 1 $telling telling 1 $told told 0 $true true 0 $univ '=..' 2 $var var 1 $version version 0 $write write 1 $lt '<' 2 $le '=<' 2 $gt '>' 2 $ge '>=' 2 $eq '==' 2 $metalt @< 2 $metale @=< 2 $metage @>= 2 $metagt @> 2 $ne '\==' 2 $eqv '=:=' 2 $neqv '=\=' 2 $match '=' 2 $nomatch '\=' 2 $end /* Initializing operators */ '?-'(op(255,fy,'?-')). ?- op(255,xfy,':-'). ?- op(255,xf,'-->'). ?- op(255,xfy,'-->'). ?- op(254,xfy,';'). ?- op(253,xfy,'->'). ?- op(252,fy,spy). ?- op(252,fy,nospy). ?- op(251,xfy,','). ?- op(249,fy,dcl). ?- op(249,fy,help). ?- op(249,fy,not). ?- op(249,fy,'\+'). ?- op(40,xfy,is). ?- op(40,xfy,'=..'). ?- op(40,xfy,=). ?- op(40,xfy,\=). ?- op(40,xfy,<). ?- op(40,xfy,=<). ?- op(40,xfy,>=). ?- op(40,xfy,>). ?- op(40,xfy,==). ?- op(40,xfy,\==). ?- op(40,xfy,=:=). ?- op(40,xfy,=\=). ?- op(40,xfy,@<). ?- op(40,xfy,@=<). ?- op(40,xfy,@>=). ?- op(40,xfy,@>). %?- op(31,yfx,/\). %?- op(31,yfx,\/). ?- op(21,yfx,+). ?- op(21,yfx,-). ?- op(21,yfx,/). ?- op(21,yfx,div). ?- op(21,yfx,*). %?- op(21,yfx,>>). %?- op(21,yfx,<<). ?- op(10,xfy,'mod'). ?- op(10,xfy,'^'). ?- op(5,fy,'+'). ?- op(5,fy,'-'). /* Defining extended predicates */ 'nospy'((Spy,Spies)) :- !, 'nospy'(Spy), 'nospy'(Spies). 'nospy'(Name/Arity) :- !, 'nospy'(Name,Arity). 'nospy'(Name) :- 'nospy'(Name,0), 'nospy'(Name,1), 'nospy'(Name,2), 'nospy'(Name,3), 'nospy'(Name,4), 'nospy'(Name,5), 'nospy'(Name,6), 'nospy'(Name,7), 'nospy'(Name,8), 'nospy'(Name,9). 'spy'((Spy,Spies)) :- !, 'spy'(Spy), 'spy'(Spies). 'spy'(Name/Arity) :- !, 'spy'(Name,Arity). 'spy'(Name) :- 'spy'(Name,0), 'spy'(Name,1), 'spy'(Name,2), 'spy'(Name,3), 'spy'(Name,4), 'spy'(Name,5), 'spy'(Name,6), 'spy'(Name,7), 'spy'(Name,8), 'spy'(Name,9). public((Public,Publics)) :- !, public(Public), public(Publics). public(Name/Arity) :- !, public(Name,Arity). public(Name) :- public(Name,0), public(Name,1), public(Name,2), public(Name,3), public(Name,4), public(Name,5), public(Name,6), public(Name,7), public(Name,8), public(Name,9). statistics(runtime, [0,X]) :- !, clock(X). statistics(garbage_collection, [0,0,0]) :- !.