# # $Id: prolog-eng.txt,v 1.2 2002/08/30 10:02:22 katsu Exp $ # This is a partial (50% so far) translation in English of the manual # (http://www.sra.co.jp/people/aoki/SmalltalkGoodies/VisualWorks/Prolog.txt) # of Prolog interpreter # (http://www.sra.co.jp/people/aoki/SmalltalkGoodies/VisualWorks/Prolog.st) # . # # Most part may be applicaple to Prolog in Jun, also. # # Translated by "WATANABE Katsuhiro" . # Prolog Goodies for VisualWorks 5i, VisualWave 3.1 / 3.0, and VisualWorks 2.5 Copyright (c) 1995-2000 AOKI Atsushi 2000/08/29 Abstract: This is a subset of DEC-10 Prolog. It is a real Prolog system and has capabilities of unification and backtracking, though op-predicate is not supported and the notation is restricted to prefix only. You can enjoy Prolog programming really-trully with it. How to Install: File in the file "Prolog.st". Then you will find a new category "Goodies-Prolog" and 16 classes in it. Also, 9 instance methods will be appended in "prolog" protocol in Object class. Following list is a summary of the changeset. Added classes: PrologBody PrologCharMap PrologClause PrologDefinition PrologEntity PrologInterpreter PrologList PrologObject PrologParser PrologScanner PrologScannerTable PrologString PrologStructure PrologSymbol PrologTerms PrologVariable Method changes: Object Added methods: car cdr cons: consp isPrologEntity isPrologVariable printPrologOn: printPrologOn:level: printPrologString If you want to un-install this goodies, just remove above classes and methods. How to use: First, you can open a window to interact with a Prolog interpreter as follows. PrologInterpreter open. The top pane is user's space to command the interpreter, and bottom one is interpreter's space to reply the user. You may enter any strings, which supposed to be clauses and goals in user's space. In order to invoke the interpreter, select appropriate part in the user's space, and choose "do it" in the yellow (or middle) button menu. Then you will find the result in the interpreter's space. For example, type the following in the user's space and do it. It means a query asking what X and Y are such that make [1,2,3,4] if they are appended. ?- append(X,Y,[1,2,3,4]). Try answering "no" for all the dialogs which pop up one after another. You can see the reply from the interpreter as follows in the bottom pane. ?- append(X,Y,[1,2,3,4]). X = [] , Y = [1,2,3,4] ; X = [1] , Y = [2,3,4] ; X = [1,2] , Y = [3,4] ; X = [1,2,3] , Y = [4] ; X = [1,2,3,4] , Y = [] ; no All the supported predicates can be enumerated by "?- predicates(User)." and "?- predicates(System)." See the attatched manual for more details. You may not want to use the user interface when you are programming in the Smalltalk. In this case, just send "refute: aString" message to an instance of PrologInterpreter, then it tries derivation and return m.g.u. for a successful refutation or return false if it fails. The result m.g.u. is expressed as an instance of Dictionary. Another programming interface of Prolog Interpreter is "refute: aString action: aBlock". If you send the message, the interpreter tries derivation of aString repeatedly with backtracking while aBlock evaluates to false. Now, let's see some examples. Firstly, "do it" the following expression in a Smalltalk workspace etc. Then you'll see "X = [3,4]" in the Transcript window. (Prolog refute: '?-append([1,2], X, [1,2,3,4]).') keysAndValuesDo: [:varname :value | Transcript show: varname, '=', value printPrologString; cr] In order to prepare for more complicated examples, create an Prolog interpreter, bind it to the Global variable "Prolog", and give it some knowledge as follows. Prolog := PrologInterpreter new. Prolog refute: ' likes(john, mary). likes(john, wine). likes(mary, wine). likes(mary, john).'. The code below enumerates who likes whom until you reply yes to the dialog saying "All right?". Prolog refute: '?-likes(X,Y).' action: [:answer | "Each time an anser is derived successfully, this block will be evaluated. If this block evaluates to false, the interpreter will backtrack and search another answer." Transcript show: answer printString; cr. Dialog confirm: 'All right?']. The code below enumerates whom both John and Mary like. | result | result := Prolog refute: '?-likes(john,X),likes(mary,X).' action: [:answer | Transcript show: answer printString; cr. Dialog confirm: 'All right?']. Transcript show: result printString; cr You can embed Smalltalk expressions in Prolog clauses and convey the Smalltalk's result value into Prolog. The portion embraced with "{}" is evaluated by Smalltalk and the value will become an constant in Prolog. Thereafter, you can send a Smalltalk message to the Smalltalk object with "send" predicate within Prolog. PrologInterpreter new refute: ' image({Image fromUser}). point({50@50}). point({100@100}). point({150@150}). ?- image(I), point(P), send(I, displayOn:at:, [{ScheduledControllers activeController view graphicsContext}, P]). % "Send" predicate have 3 arguments. They are, the Smalltalk Object, the message selector and the list of arguments for the message. ' action: [:answer | Dialog confirm: 'All right?'] An example of pseudo high order predicate "is" follows. PrologInterpreter new refute: ' sorryThisDoesNotTakeEffect(12,3). % But not really high order. ?-is(Z,F(12,3)).' action: [:answer | Transcript show: answer printString; cr. false] In case you want to unify two terms expressed as strings, try the code below. | unification result prolog | prolog := PrologInterpreter new. unification := [:term1 :term2 | "Return the m.g.u. of term1 and term2, or false if unification fails." | parser pterm1 pterm2 valueEnv successFlag | parser := PrologParser new. pterm1 := (parser on: (ReadStream on: term1)) scanExpression. pterm2 := (parser on: (ReadStream on: term2)) scanExpression. valueEnv := prolog resolveInitialize; nullEnv. successFlag := prolog unify: pterm1 env: valueEnv and: pterm2 env: valueEnv. successFlag ifFalse: [false] ifTrue: [ "Unification finished successfully. But there are unnecessary temporal variables which don't show in term1 nor term2. Filter them out." | variableDict| variableDict := Dictionary new. prolog collectVariables: pterm1 to: variableDict. prolog collectVariables: pterm2 to: variableDict. variableDict keys do: [:varName | | prologVar varValue | prologVar := PrologVariable install: varName. varValue := prolog represent: prologVar env: valueEnv. variableDict at: varName put: varValue printPrologString]. variableDict]]. "Usage:" result := unification value: 'f(X, g(Y))' value: 'f(g(Y), h(X))'. Transcript show: result printString; cr. result := unification value: 'f(X, h(0))' value: 'f(g(Y), Y)'. Transcript show: result printString; cr "The interpreter omits occurence check as usual inplementation of Prolog. Hence, unification of X and f(X) will never terminate, for instance." ------------------------------------------------------------ 青木淳(AOKI Atsushi) http://www.sra.co.jp/people/aoki Software Research Associates, Inc. mailto:aoki@sra.co.jp Marusho-Bldg.5F, 3-12 Yotsuya, Tel:03-3357-9361 Shinjuku-ku, Tokyo 160-0004, JAPAN Fax:03-3351-0880 ------------------------------------------------------------ Prolog manual This is a subset of DEC-10 Prolog. It is a real Prolog system and has capabilities of unification and backtracking, though op-predicate is not supported and the notation is restricted to prefix only. You can enjoy Prolog programming really-trully with it. Constant  There are 5 kinds of constants in this Prolog, to say: Atom Number String List Object An atom normally starts from a lowercase letter and followed by lowercase, uppercase or numeric letters. You can include special characters in an atom, provided you quote the atom with "'". If you want to include "'" itself, double it as "''". aoki atsushi symbol12345 'AOKI Atsushi' 'You are ''cool''.' Numbers are expressed just as Smalltalk number literals. 123 -123 123.456 -123.456 123.456e7 -123.456e-7 16r123 Strings are expressed with two double quote(") characters at its head and tail. If you include (") in a string, you have to double it as (""). "AOKI Atushi" "You are ""cool""." List is constructed with "[", "|", "]", and ",". "[]" is an empty list. "[AOKI|Atsushi]" is an instance of a dotted pair whose head is "AOKI" and whose tail is "Atsushi". In turn, the tail of "[AOKI, Atsushi]" is a list "[Atsushi]", while its head is still "AOKI". Hence "[AOKI,Atsushi]" is equal to "[AOKI|[Atsushi]]". "[]" represents nil in Smalltalk. [] [AOKI|Atsushi] [AOKI,Atsushi] [AOKI|[Atsushi]] Smalltalk expression embraced with "{}" are handled as object constant in this Prolog. The embraced part is evaluated by Smalltalk system and the result value becomes an constant in Prolog. "{}" is identical to "{nil}". {100@100} {Image fromUser} {('aaa') at: 2 put: $z; yourself} Variable Variable name starts with uppercase letter and followed by alphanumeric characters. "~" is the special variable called anonymous variable. AOKI Atsushi Variable1234 ~ Anonymous variable may be used where you have to put a variable but you don't bother the value at all. Assume you need to confirm that there is someone in the world who likes smalltalk but you don't bother the concrete person who likes it. The goal shown below checks that condition. likes(aoki,smalltalk). likes(aoki,prolog). likes(watanabe,smalltalk). likes(watanabe,lisp). likes(sakoh,lisp). likes(sahara,prolog). ?- likes(~,smalltalk). yes ?- likes(~,prolog). yes ?- likes(~,lisp). yes ?- likes(~,c). no As shown above, "?- likes(~,prolog)" and "?- likes(~,lisp)", which asks if there is someone who likes prolog (or lisp), will success. But "?- likes(~,c)", which asks if there is someone who likes c, will fail, that means no one likes c. Those who are accustomed to programming in Prolog may suspect why the name of anonymous variable is "~", not commonly used "_"(underbar). In some Smalltalk implementations (mainly historic ones), "_" are used to express substitution. And there are other Smalltalk implementations (mainly modern ones) in which you can include underbars in message selector. If we stuck to underbar for anonymous variable's name, you would be somewhat confused to interface between Smalltalk and Prolog. System Predicate The Prolog interpreter has some knowledge in advance at the startup time. They are called system predicates and categorized into following 10 groups. Builtin system predicates(systemPredicatesNo0) Basic system predicates(systemPredicatesNo1) Comparison system predicates(systemPredicatesNo2) Arithmetic system predicates(systemPredicatesNo3) Term and clause system predicates(systemPredicatesNo4) Higher order system predicates(systemPredicatesNo5) I/O system predicates(systemPredicatesNo6) Debugging system predicates(systemPredicatesNo7) Miscelleany system predicates(systemPredicatesNo8) User defined system predicates(systemPredicatesNo9) See the following description for more details about these 10 groups. Builtin system predicates(systemPredicatesNo0) ! Cut(predicate !) always succeeds. But it has a drastic side effect. Assume there are some horn clauses that have same head part (ignoreing the difference of variable names) and the interpreter is trying to derive the subgoal (the body part of the clause) of one of these similar clauses. In ordinal cases without cut, if the derivation fails, then the interpreter backtracks to the point where the interpreter selects next alternative clauses and the derivation goes on. But if the interpreter enconters a cut in the subgoal, it forgets all the alternatives. Consequently, when a backtracking occurs in the clause in question, the interpreter will not find any alternatives and the derivation of the subgoal must fail. Cut is usefull in two points. First, you can promote efficiency of the axiom system of your horn clauses by skipping alternative subgoals when backtrack is supposed to occur. Second you can save memory space by not retaining alternatives for backtrack. But you have to discipline yourself to use cut properly, because cut nullifies the significance of backtrack feature. There are three major reasons to use cut: (1) You want to tell the intepreter that you've found a correct path to refute the goal. (2) You want to make the goal fail immediately. (3) You have already got an answer and don't want to get another with backtracking. true True predicate always succeeds. Its reason of being is just to keep integrity of the system predicate set, considering the complement of the fail predicate. There may be no chance to use this predicate in real programming scene. fail Fail predicate always fails. Its common use is to abandon the current derivation and force backtracking intentionally. Let's see one of the most popular example of its use; You are able to get all the solutions for append(X,Y,[1,2,3]) by: output(X,Y) :- write(X), write(", "), write(Y), nl. ?- append(X,Y,[1,2,3]), output(X,Y), fail. The above goal clause figures out a solution (X,Y), output the pair, and then backtracks by fail in order to search another solution. Backtracking continues until all the solutions are figured out. Another common use of fail can be seen in combination with cut(!). "..., !, fail." is a popular idiom meaning that it is enough if I get "...". The following definition of not(G), ,is an application of this idiom:  常に失敗する述語です。故意に後戻り(バックトラック)を起こすこと ができるので,使用する場面が多かろうと思います。たとえば, append(X,Y,[1,2,3])の目標に対するすべての解を求めたい場合には, 次のようになります。 output(X,Y) :- write(X), write(", "), write(Y), nl. ?- append(X,Y,[1,2,3]), output(X,Y), fail.  このプログラムは,充足したXとYをoutput(X,Y)で出力させ,その後 のfailよって後戻りを起こさせ,XとYに充足可能なすべての解を求めて います。  また,カット(!)との組み合わせも有効です。「…, !, fail.」は 「実行がここまで進んだらもうよい(もう結構)」ということを表わして います。たとえば,ある目標Gが充足したことを否定する述語not(G)は, カット(!)と失敗(fail)を組み合わせて,以下のように記述することが できます。 not(G) :- call(G), !, fail. not(G).  第一の節を実行している間に目標Gが失敗すれば,「…, !, fail.」 に届く前に後戻りが起こり,第二の節の「not(G).」が充足され,目標G が成功したことになります。反対に,第一の節を実行している間に目標 Gが成功すれば,それまでの選択枝が!によって除去され,その後のfail によって第一の節が失敗し,結局のところ目標Gが失敗したことになり ます。 var(X)  Xが代入されていない変数の時に成功します。 ?- is(X,100), var(X). no ?- is(X,Y), var(X). X = X3 , Y = X3 yes  ある変数が代入されていない時に,ユーザに入力をうながすには, 「…, var(X), read(X), …」というイディオムが便利です。 send(X,Y,Z) send(X,Y,Z,A)  Smalltalkのメッセージを送信する述語です。Xをレシーバにして,Y というメッセージを,Zという引数リストを付けて送信し,その結果をA にユニファイします。レシーバに「self」の記号を指定すると,Prolog のインタプリタのインスタンス(a PrologInterpreter)がレシーバにな ります。 image({Image fromUser}). point({50@50}). point({100@100}). point({150@150}). gc({ScheduledControllers activeController view graphicsContext}). ?- image(Image), point(Point), gc(GraphicsContext), send(Image,displayOn:at:,[GraphicsContext,Point],Image). 基本的なシステム述語(systemPredicatesNo1) repeat  繰り返しを行なう述語です。 nonvar(X)  Xが未代入の変数であれば成功し,代入済みの変数もしくは定数なら ば失敗します。 integer(X)  Xが整数ならば成功し,それ以外ならば失敗します。 float(X)  Xが単精度浮動小数点数ならば成功し,それ以外ならば失敗します。 double(X)  Xが倍精度浮動小数点数ならば成功し,それ以外ならば失敗します。 fraction(X)  Xが分数ならば成功し,それ以外ならば失敗します。 number(X) :- send(self,number:,[X]).  Xが数ならば成功し,それ以外ならば失敗します。 symbol(X) :- send(self,symbol:,[X]).  Xが記号ならば成功し,それ以外ならば失敗します。 string(X) :- send(self,string:,[X]).  Xが文字列ならば成功し,それ以外ならば失敗します。 list(X) :- send(self,list:,[X]).  Xがリストならば成功し,それ以外ならば失敗します。空リストは成 功します。 dotp(X)  Xがセル(ドットペア)ならば成功し,それ以外ならば失敗します。 空リストは失敗します。 atom(X)  Xがアトムならば成功し,それ以外ならば失敗します。アトムとは, 記号,文字列,空リストのことです。 atomic(X)  Xがアトムまたは数ならば成功し,それ以外ならば失敗します。 structure(X)  Xがアトムまたは数ならば失敗し,それ以外ならば成功します。 比較演算に関するシステム述語(systemPredicatesNo2) ==(X,Y) :- send(X,=,[Y]).  SmalltalkでXとYが等しいとき成功し,それ以外ならば失敗します。 \==(X,Y) :- ==(X,Y), !, fail.  SmalltalkでXとYが等しいとき失敗し,それ以外ならば成功します。 =(X,X)  XとYが等しいとき成功し,それ以外ならば失敗します。 \=(X,Y)  XとYが等しいとき失敗し,それ以外ならば成功します。 >(X,Y)  XがYより大きいならば成功し,それ以外ならば失敗します。 >=(X,Y)  XがYより大きいか等しいならば成功し,それ以外ならば失敗します。 <(X,Y)  XがYより小さいならば成功し,それ以外ならば失敗します。 =<(X,Y)  XがYより小さいか等しいならば成功し,それ以外ならば失敗します。 算術演算に関するシステム述語(systemPredicatesNo3) +(X,Y,Z)  XとYを加算したものがZと等しいならば成功し,それ以外ならば失敗 します。 -(X,Y,Z)  XとYを減算したものがZと等しいならば成功し,それ以外ならば失敗 します。 *(X,Y,Z)  XとYを乗算したものがZと等しいならば成功し,それ以外ならば失敗 します。 //(X,Y,Z)  XとYを除算して余りを切り捨てたものがZと等しいならば成功し,そ れ以外ならば失敗します。 /(X,Y,Z)  XとYを除算したものがZと等しいならば成功し,それ以外ならば失敗 します。 \\(X,Y,Z)  XとYをモジュロ演算したものがZと等しいならば成功し,それ以外な らば失敗します。 is(X,Y)  XとYが等しいとき成功し,それ以外ならば失敗します。 is(Z,F(X,Y))  加減乗除において,XとYを加減乗除したものがZと等しいならば成功 し,それ以外ならば失敗します。 節や項に関するシステム述語(systemPredicatesNo4) listing  登録されているすべての述語の節を出力し,常に成功します。 listing(X)  Xで指定される記号を述語としてもつ節を出力し,成功します。対応 する述語がないならば失敗します。 systemListing  登録されているすべてのシステム述語の節を出力し,常に成功します。 systemListing(X)  Xで指定される記号をシステム述語としてもつ節を出力し,成功しま す。対応するシステム述語がないならば失敗します。 editing  登録されているすべての述語を編集するエディタを開き,常に成功し ます。 consult  Prologのプログラムを読み込むためのウィンドウが開き成功します。 このウィンドウ内でPrologのプログラムを書き,acceptすると,書かれ た節を最後に追加します。 consult(X)  Xで指定されるファイルからPrologのプログラムを読み込み,読み込 んだ節を最後に追加し,成功します。対応するファイルが存在しないな らば失敗します。 reconsult  Prologのプログラムを読み込むためのウィンドウが開き成功します。 このウィンドウ内でPrologのプログラムを書き,acceptすると,書かれ た節をこれと同じ述語の節に置き換えます。 reconsult(X)  Xで指定されるファイルからPrologのプログラムを読み込み,読み込 んだ節をこれと同じ述語の節に置き換え,成功します。対応するファイ ルが存在しないならば失敗します。 saving  登録されているすべての述語の節を入力ダイアログで指定されたファ イルへ出力し,常に成功します。 saving(X)  Xで指定される記号を述語としてもつ節を入力ダイアログで指定され たファイルへ出力し,成功します。対応する述語がないならば失敗しま す。 userPredicates(X)  登録されているすべての述語をリストにしてXとユニファイします。 systemPredicates(X)  登録されているすべてのシステム述語をリストにしてXとユニファイ します。 predicates([X|Y])  登録されているすべての述語をリストにしてXとユニファイし,登録 されているすべてのシステム述語をリストにしてYとユニファイします。 functor(T,F,A)  この述語は,Tが関数子FとN個の引数をもつ構造を意味します。 ?- functor(likes(aoki,smalltalk),F,N). F = likes , N = 2 yes ?- functor(aoki,F,N). F = aoki , N = 0 yes arg(N,S,T)  この述語は,構造SのN番目の引数がTであることを意味します。常に NとSが代入されていなければなりません。 ?- arg(2,likes(aoki,smalltalk),A). A = smalltalk yes =..(X,L)  この述語は「ユニブ」と呼ばれ,LはXの関数子と引数からなるリスト を意味します。 ?- =..(likes(aoki,smalltalk),L). X = [likes,aoki,smalltalk] yes ?- =..(X,[likes,aoki,smalltalk]). X = likes(aoki,smalltalk) yes name(A,L)  記号Aの文字列はリストLであることを意味します。 ?- name(apple,L). L = "apple" yes ?- name(A,[97,112,112,108,101]). A = apple yes ?- name(A,"apple"). A = apple yes remove  登録されているすべての述語の節を削除します。この述語は常に成功 します。 remove(X)  Xで指定される記号を述語としてもつ節を削除し,成功します。対応 する述語がないならば失敗します。 clause(X)  Xで指定される節を登録されている節にユニファイします。 concat([],X,X). concat([A|X],Y,[A|Z]) :- concat(X,Y,Z). ?- clause([[concat|Arguments]|Body]). Arguments = ([],X6,X6) , Body = [] ; Arguments = ([A11|X11],Y11,[A11|Z11]) , Body = concat(X11,Y11,Z11) ; no ?- clause([concat(|Arguments)|Body]). Arguments = ([],X6,X6) , Body = [] ; Arguments = ([A11|X11],Y11,[A11|Z11]) , Body = concat(X11,Y11,Z11) ; no asserta(X)  Xで指定される節をその述語で示される節の先頭に加えます。 ?- remove, asserta([likes(aoki,smalltalk)]), asserta([likes(watanabe,smalltalk)]), listing. likes(watanabe,smalltalk). likes(aoki,smalltalk). yes assert(X) assertz(X)  Xで指定される節をその述語で示される節の末尾に加えます。 ?- remove, assertz([on(cat,dog)]), asserta([on(hen,cat)]), assertz([on(dog,donkey)]), assertz([above(X,Y) :- on(X,Y)]), assertz([above(X,Y) :- on(X,Z), above(Z,Y)]), listing. ?- above(X,dog). above(X,Y) :- on(X,Y). above(X,Y) :- on(X,Z), above(Z,Y). on(hen,cat). on(cat,dog). on(dog,donkey). X = X1 , Y = Y1 , Z = Z1 yes ?- above(X,dog). X = cat ; X = hen ; no retract(X)  Xで指定される節を登録されている節にユニファイし,成功すると, その節は削除されます。 concat([],X,X). concat([A|X],Y,[A|Z]) :- concat(X,Y,Z). ?- listing(concat). % ちゃんと登録されているかな concat([],X,X). concat([A|X],Y,[A|Z]) :- concat(X,Y,Z). yes ?- retract([concat(|Arguments)|Body]). % 消すぞ Arguments = ([],X6,X6) , Body = [] ; Arguments = ([A11|X11],Y11,[A11|Z11]) , Body = concat(X11,Y11,Z11) ; no ?- listing(concat). % もうなくなっているはず no 高階のシステム述語(systemPredicatesNo5) call(G)  Gを目標として充足できるならば成功となり,充足できないならば失 敗となります。 not(G)  Gを目標として充足できるならば失敗となり,充足できないならば成 功となります。 or(X,Y)  XとYの選言を表わします。Xが成功するかまたはYが成功すれば,選言 は成功となります。Xが失敗の時に,Yの充足が試みられます。この時, Yも失敗すると選言が失敗をします。 and(X,Y)  XとYの連言を表わします。Xが成功しかつYも成功するならば,連言は 成功となります。Xが成功したのに,Yが失敗すると,Xの再充足が試み られます。 入出力に関するシステム述語(systemPredicatesNo6) read(X)  入力ダイアログから入力をXとユニファイします。 read(X,M)  入力ダイアログから入力をXとユニファイします。その際に,入力ダ イアログのメッセージとしてMを使用します。 write(X)  Xを出力します。常に成功する述語です。 nl  復改を出力します。常に成功する述語です。 tab(X)  タブをXだけ出力します。Xが代入されていないならば失敗します。 clear  出力をきれいにします。常に成功する述語です。 デバッグのためのシステム述語(systemPredicatesNo7) clock(X)  現在の時刻をミリ秒単位でXにユニファイします。 verbose(X)  Xがtrueという記号の場合に,充足にかかった時間と試みたゴールの 数を出力します。Xがtrueという記号以外ならば,時間とゴール数の出 力を停止します。 ?- remove. above(X,Y) :- on(X,Y). above(X,Y) :- on(X,Z), above(Z,Y). on(hen,cat). on(cat,dog). on(dog,donkey). ?- verbose(true). ?- above(X,donkey). ?- verbose(false). ?- remove. yes ?- verbose(true). <0 milliseconds, 1 goals> yes ?- above(X,donkey). <0 milliseconds, 4 goals> X = dog ; <0 milliseconds, 17 goals> X = hen ; <0 milliseconds, 35 goals> X = cat ; <16 milliseconds, 56 goals> no ?- verbose(false). yes gc  ガベジコレクションを行ないます。この述語は常に成功します。 inspect(X)  Xをインスペクションします。この述語は常に成功します。 spy(X)  Xで指定される記号を述語としてもつ節のトレースを開始します。 nospy(X)  Xで指定される記号を述語としてもつ節のトレースを終了します。 trace  登録されているすべての節のトレースを開始します。 notrace  登録されているすべての節のトレースを終了します。 その他のシステム述語(systemPredicatesNo8) append(X,Y,Z)  XとYを接続したリストがZであることを意味します。 member(X,Y)  XがYのリストの要素であることを意味します。 reverse(X,Y)  XのリストのリバースがYのリストであることを意味します。 length(X,Y)  Xのリストの長さがYであることを意味します。 nth(X,Y,Z)  XのリストのY番目の要素がZであることを意味します。 printlist(L)  Lのリストの要素を順番に出力します。 lispAppend(X,Y,Z) lispReverse(X,Y) lispMember(X,Y) lispMember(X,Y,Z) lispAssoc(X,Y) lispAssoc(X,Y,Z) lispNconc(X,Y,Z)  これらはLispの関数を呼び出す述語で,高速ですが,後戻り(バック トラック)できません。 ユーザ定義のシステム述語(systemPredicatesNo9)  現在,ユーザ定義のシステム述語はありませんが,皆さんで作成して, ここに,その機能をお書き下さい。 システム述語一覧 ! (systemPredicatesNo0) * (systemPredicatesNo3) + (systemPredicatesNo3) - (systemPredicatesNo3) / (systemPredicatesNo3) // (systemPredicatesNo3) < (systemPredicatesNo2) = (systemPredicatesNo2) =.. (systemPredicatesNo4) =< (systemPredicatesNo2) == (systemPredicatesNo2) > (systemPredicatesNo2) >= (systemPredicatesNo2) and (systemPredicatesNo5) append (systemPredicatesNo8) arg (systemPredicatesNo4) assert (systemPredicatesNo4) asserta (systemPredicatesNo4) assertz (systemPredicatesNo4) atom (systemPredicatesNo1) atomic (systemPredicatesNo1) call (systemPredicatesNo5) clause (systemPredicatesNo4) clear (systemPredicatesNo6) clock (systemPredicatesNo7) consult (systemPredicatesNo4) dotp (systemPredicatesNo1) double (systemPredicatesNo1) editing (systemPredicatesNo4) fail (systemPredicatesNo0) float (systemPredicatesNo1) fraction (systemPredicatesNo1) functor (systemPredicatesNo4) gc (systemPredicatesNo7) inspect (systemPredicatesNo7) integer (systemPredicatesNo1) is (systemPredicatesNo3) length (systemPredicatesNo8) lispAppend (systemPredicatesNo8) lispAssoc (systemPredicatesNo8) lispMember (systemPredicatesNo8) lispNconc (systemPredicatesNo8) lispReverse (systemPredicatesNo8) list (systemPredicatesNo1) listing (systemPredicatesNo4) member (systemPredicatesNo8) name (systemPredicatesNo4) nl (systemPredicatesNo6) nonvar (systemPredicatesNo1) nospy (systemPredicatesNo7) not (systemPredicatesNo5) notrace (systemPredicatesNo7) nth (systemPredicatesNo8) number (systemPredicatesNo1) or (systemPredicatesNo5) predicates (systemPredicatesNo4) printlist (systemPredicatesNo8) read (systemPredicatesNo6) reconsult (systemPredicatesNo4) remove (systemPredicatesNo4) repeat (systemPredicatesNo1) retract (systemPredicatesNo4) reverse (systemPredicatesNo8) saving (systemPredicatesNo4) send (systemPredicatesNo0) spy (systemPredicatesNo7) string (systemPredicatesNo1) structure (systemPredicatesNo1) symbol (systemPredicatesNo1) systemListing (systemPredicatesNo4) systemPredicates (systemPredicatesNo4) tab (systemPredicatesNo6) trace (systemPredicatesNo7) true (systemPredicatesNo0) userPredicates (systemPredicatesNo4) var (systemPredicatesNo1) verbose (systemPredicatesNo7) write (systemPredicatesNo6) \= (systemPredicatesNo2) \== (systemPredicatesNo2) \\ (systemPredicatesNo3) Copyright (c) 1995-2000 AOKI Atsushi