Object subclass: #PrologModoki instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Practice-PrologModoki'! !PrologModoki commentStamp: 'sumim 5/16/2003 02:12' prior: 0! I behave myself like a Prolog program such as ... grandparent(A,B) :- parent(A,C),parent(C,B). father(F,C) :- male(F),parent(F,C). parent(tom,jane). parent(tom,jim). parent(mary,jane). parent(jack,sam). parent(jane.sam). parent(jim.bob). parent(betty,bob). male(tom). male(jack). male(jim). male(sam). male(bob). female(mary). female(jane). female(betty). " PrologModoki male: #jack and: [^ true] PrologModoki female: #jack and: [^ true] PrologModoki female: #mary and: [^ true] " ?- male(X). " | result results | results _ OrderedCollection new. PrologModoki male: (result _ PrologModoki var new) and: [results add: result value]. ^ results " ?- female(X). " | result results | results _ OrderedCollection new. PrologModoki female: (result _ PrologModoki var new) and: [results add: result value]. ^ results " ?-parent(X,bob). " | result results | results _ OrderedCollection new. PrologModoki parent: (result _ PrologModoki var new) of: #bob and: [results add: result value]. ^ results " ?-father(X,bob). " | results result | results _ OrderedCollection new. PrologModoki father: (result _ PrologModoki var new) of: #bob and: [results add: result value]. ^ results " ?-grandparent(X,sam). " | result results | results _ OrderedCollection new. PrologModoki grandParent: (result _ PrologModoki var new) of: #sam and: [results add: result value]. ^ results " ?-factorial(100,X). " | x | PrologModoki factorial: 100 is: (x _ PrologModoki var new) and: [^ x value] " ?-search(1,a,[]). %Knight's Tour " PrologModoki search: 1 position: #a path: #() and: [^ true] "! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! PrologModoki class instanceVariableNames: ''! !PrologModoki class methodsFor: 'private' stamp: 'sumim 5/15/2003 03:24'! doesNotUnderstand: aMessage ^ false! ! !PrologModoki class methodsFor: 'private' stamp: 'sumim 5/15/2003 14:29'! var ^ PrologModokiVariable! ! !PrologModoki class methodsFor: 'private' stamp: 'sumim 5/15/2003 12:24'! vars: aColleciton ^ PrologModokiVariables withAll: aColleciton! ! !PrologModoki class methodsFor: 'family' stamp: 'sumim 5/15/2003 14:14'! father: personA of: personB and: aBlock " father(A,B) :- male(A),parent(A,B). " self male: personA and: [self parent: personA of: personB and: [aBlock value]]. ^ false! ! !PrologModoki class methodsFor: 'family' stamp: 'sumim 5/15/2003 14:14'! female: person and: aBlock | vars continuation savedVars | vars _ self vars: {person}. savedVars _ vars copy. continuation _ [aBlock value. vars failed: savedVars]. person = #mary and: continuation. person = #jane and: continuation. person = #betty and: continuation. ^ false! ! !PrologModoki class methodsFor: 'family' stamp: 'sumim 5/15/2003 14:29'! grandParent: personA of: personB and: aBlock " grandparent(A,B) :- parent(A,C),parent(C,B). " | personC | self parent: personA of: (personC _ self var new) and: [ self parent: personC of: personB and: [aBlock value]]. ^ false! ! !PrologModoki class methodsFor: 'family' stamp: 'sumim 5/15/2003 14:14'! male: person and: aBlock | vars continuation savedVars | vars _ self vars: {person}. savedVars _ vars copy. continuation _ [aBlock value. vars failed: savedVars]. person = #tom and: continuation. person = #jack and: continuation. person = #jim and: continuation. person = #sam and: continuation. person = #bob and: continuation. ^ false! ! !PrologModoki class methodsFor: 'family' stamp: 'sumim 5/15/2003 14:15'! parent: personA of: personB and: aBlock | vars continuation savedVars | vars _ self vars: {personA. personB}. savedVars _ vars copy. continuation _ [aBlock value. vars failed: savedVars]. vars = #(tom jane) and: continuation. vars = #(tom jim) and: continuation. vars = #(mary jane) and: continuation. vars = #(mary jim) and: continuation. vars = #(jack sam) and: continuation. vars = #(jane sam) and: continuation. vars = #(jim bob) and: continuation. vars = #(betty bob) and: continuation. ^ false! ! !PrologModoki class methodsFor: 'factorial' stamp: 'sumim 5/15/2003 14:33'! factorial: n is: x and: aBlock | vars savedVars continuation x1 | vars _ self vars: {x}. savedVars _ vars copy. continuation _ [aBlock value. vars failed: savedVars]. n < 2 and: [x = 1 and: continuation]. self factorial: n - 1 is: (x1 _ self var new) and: [x = (n * x1) and: continuation]! ! !PrologModoki class methodsFor: 'knight''s tours' stamp: 'sumim 5/15/2003 21:17'! jump: cellA to: cellB and: aBlock self next: cellA is: cellB and: [aBlock value]. self next: cellB is: cellA and: [aBlock value]. ^ false! ! !PrologModoki class methodsFor: 'knight''s tours' stamp: 'sumim 5/16/2003 00:26'! next: cellA is: cellB and: aBlock | vars savedVars continuation | vars _ self vars: {cellA. cellB}. savedVars _ vars copy. continuation _ [aBlock value. vars failed: savedVars]. vars = #(a f) and: continuation. vars = #(a h) and: continuation. vars = #(b g) and: continuation. vars = #(b i) and: continuation. vars = #(c d) and: continuation. vars = #(c h) and: continuation. vars = #(d i) and: continuation. vars = #(d k) and: continuation. vars = #(e j) and: continuation. vars = #(e l) and: continuation. vars = #(f g) and: continuation. vars = #(f k) and: continuation. vars = #(g l) and: continuation. vars = #(i j) and: continuation. ^ false! ! !PrologModoki class methodsFor: 'knight''s tours' stamp: 'sumim 5/16/2003 02:10'! search: n position: position path: path and: aBlock | vars continuation savedVars nextPosition n1 | vars _ self vars: {n. position. path}. savedVars _ vars copy. continuation _ [aBlock value. vars failed: savedVars]. vars = {12. position. path} and: [[ World findATranscript: nil. Transcript cr; show: path, {position}. false] value and: continuation]. self jump: position to: (nextPosition _ self var new) and: [ (path includes: nextPosition value) not and: [ (n1 _ self var new) = (n + 1) and: [ self search: n1 position: nextPosition value path: path, {position} and: continuation]]]. ^ false! ! Object variableSubclass: #PrologModokiVariable instanceVariableNames: 'value ' classVariableNames: '' poolDictionaries: '' category: 'Practice-PrologModoki'! !PrologModokiVariable commentStamp: 'sumim 5/15/2003 18:37' prior: 0! I am a variable for PrologModoki program.! !PrologModokiVariable methodsFor: 'accessing' stamp: 'sumim 5/15/2003 15:04'! value ^ value! ! !PrologModokiVariable methodsFor: 'accessing' stamp: 'sumim 5/15/2003 15:02'! value: anObject value _ anObject! ! !PrologModokiVariable methodsFor: 'comparing' stamp: 'sumim 5/16/2003 01:45'! = anObject | newObject | newObject _ (anObject isKindOf: self class) ifTrue: [anObject value] ifFalse: [anObject]. value ifNil: [ self value: newObject. ^ true]. ^ value = newObject! ! !PrologModokiVariable methodsFor: 'adapting' stamp: 'sumim 5/15/2003 15:03'! adaptToInteger: rcvr andSend: selector ^ rcvr perform: selector with: value! ! !PrologModokiVariable methodsFor: 'printing' stamp: 'sumim 5/15/2003 15:02'! printOn: aStream value printOn: aStream! ! !PrologModokiVariable methodsFor: 'arithmetic' stamp: 'sumim 5/15/2003 22:10'! + aNumber ^ value + aNumber! ! Array variableSubclass: #PrologModokiVariables instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Practice-PrologModoki'! !PrologModokiVariables commentStamp: 'sumim 5/15/2003 18:38' prior: 0! I am a collection that includes PrologModokiVariables.! !PrologModokiVariables methodsFor: 'comparing' stamp: 'sumim 5/15/2003 23:33'! = aCollection self with: aCollection do: [ :a :b | (a isKindOf: PrologModoki var) ifTrue: [a value ifNotNil: [a = b ifFalse: [^ false]]] ifFalse: [a = b ifFalse: [^ false]]]. self with: aCollection do: [ :a :b | a = b ]. ^ true! ! !PrologModokiVariables methodsFor: 'comparing' stamp: 'sumim 5/16/2003 01:12'! copy | copy | copy _ super copy. self doWithIndex: [ :each :idx | (each isKindOf: PrologModoki var) ifTrue: [copy at: idx put: each value copy] ifFalse: [copy at: idx put: each copy]]. ^ copy! ! !PrologModokiVariables methodsFor: 'private' stamp: 'sumim 5/15/2003 15:07'! failed: aCollection self with: aCollection do: [ :a :b | (a isKindOf: PrologModoki var) ifTrue: [a value: b]]! !