prototypes vs classes

Dietmar Krueger dkrueger at oec.uni-osnabrueck.de
Thu Oct 22 10:22:30 UTC 1998


>>Folks -
>>
....
>>
>>I'm not saying stop talking.  I'm saying start building.
>>
>>	- Dan
>
>Yes! While waiting for results i have written this:
>
Here is my last version of a very simple prototype system. It is still just
a toy for me, but it makes it possible to translate the account example of
the Self 4.0 tutorial to Squeak (see example4 at the end):

'From Squeak 2.2 of Sept 23, 1998 on 22 October 1998 at 12:11:05 pm'!
Object subclass: #Proto
	instanceVariableNames: 'methodKeys slots '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Category-Test'!

!Proto methodsFor: 'rest' stamp: 'd.k. 10/22/1998 11:29'!
@ aSymbol
	^self at: aSymbol! !

!Proto methodsFor: 'rest' stamp: 'd.k. 10/22/1998 11:29'!
at: aSymbol
	| proto |
	proto := self lookUpSlot: aSymbol.
	proto isNil
		ifTrue:[self error: aSymbol, ' not found']
		ifFalse:[^self handleSlot: aSymbol with: proto]
		! !

!Proto methodsFor: 'rest' stamp: 'd.k. 10/22/1998 11:31'!
at: aSymbol with: anObject
	| proto |
	proto := self lookUpSlot: aSymbol.
	proto isNil
		ifTrue:[self error: aSymbol, ' not found']
		ifFalse:[^self handleSlot: aSymbol with: proto with: anObject]
		! !

!Proto methodsFor: 'rest' stamp: 'd.k. 10/22/1998 11:48'!
handleMethod: methodString
	^(Compiler evaluate: '[:proto | ', (methodString copyReplaceTokens:
'self' with: 'proto'), ']')
		value: self! !

!Proto methodsFor: 'rest' stamp: 'd.k. 10/22/1998 11:48'!
handleMethod: methodString with: anObject
	^(Compiler evaluate: '[:proto ', (methodString copyReplaceTokens:
'self' with: 'proto'), ']')
		value: self value: anObject! !

!Proto methodsFor: 'rest' stamp: 'd.k. 10/22/1998 12:01'!
handleSlot: aSymbol with: aProto
	| slotValue |
	slotValue := aProto slots at: aSymbol.
	(aProto isMethod: aSymbol)
		ifTrue:[^self handleMethod: slotValue]
		ifFalse:[^slotValue]! !

!Proto methodsFor: 'rest' stamp: 'd.k. 10/22/1998 12:03'!
handleSlot: aSymbol with: aProto with: anObject
	| slotValue |
	slotValue := aProto slots at: aSymbol.
	(aProto isMethod: aSymbol)
		ifTrue:[^self handleMethod: slotValue with: anObject]
		ifFalse:[self slots at: aSymbol put: anObject]! !

!Proto methodsFor: 'rest' stamp: 'd.k. 10/22/1998 12:00'!
lookUpSlot: aSymbol
	| proto |
	(self hasLocalSlot: aSymbol) ifTrue:[^self].
	self inheritanceKeys do: [:iKey| 	proto := (self slots at:
iKey) lookUpSlot: aSymbol.

	proto isNil ifFalse:[^proto]].
	^nil! !

!Proto methodsFor: 'rest' stamp: 'd.k. 10/22/1998 12:00'!
slots
	slots ifNil: [slots := Dictionary new].
	^slots! !


!Proto methodsFor: 'initialization' stamp: 'd.k. 10/22/1998 11:57'!
defInheritance: aSymbol to: anObject
	self defValue: (aSymbol, '*') asSymbol to: anObject! !

!Proto methodsFor: 'initialization' stamp: 'd.k. 10/22/1998 12:01'!
defMethod: aSymbol to: aString
	self methodKeys add: aSymbol.
	self slots at: aSymbol put: aString! !

!Proto methodsFor: 'initialization' stamp: 'd.k. 10/22/1998 12:01'!
defValue: aSymbol to: anObject
	(self methodKeys includes: aSymbol) ifTrue:[methodKeys remove:
aSymbol].
	self slots at: aSymbol put: anObject! !


!Proto methodsFor: 'testing' stamp: 'd.k. 10/22/1998 12:10'!
hasLocalSlot: aSymbol
	^self slots includesKey: aSymbol! !

!Proto methodsFor: 'testing' stamp: 'd.k. 10/22/1998 12:10'!
isMethod: aSymbol
	^self methodKeys includes: aSymbol! !


!Proto methodsFor: 'keys' stamp: 'd.k. 10/22/1998 12:01'!
inheritanceKeys
	^self slots keys select: [:k| k last = $*]! !

!Proto methodsFor: 'keys' stamp: 'd.k. 10/22/1998 10:43'!
methodKeys
	methodKeys ifNil: [methodKeys := Set new].
	^methodKeys! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

Proto class
	instanceVariableNames: ''!

!Proto class methodsFor: 'examples' stamp: 'd.k. 10/22/1998 11:56'!
example1
	"Proto example1"

	|person|
	person := Proto new.
	person defValue: #name to: 'Dietmar'.
	person defValue: #age to: 30.
	person defMethod: #birthday to: 'self at: #age with: self @ #age + 1'.
	person @ #birthday.
	^person @ #age
! !

!Proto class methodsFor: 'examples' stamp: 'd.k. 10/22/1998 11:56'!
example2
	"Proto example2"

	|person kunde |
	person := Proto new.
	person defValue: #name to: 'Dietmar'.
	person defValue: #age to: 30.
	person defMethod: #birthday to: 'self at: #age with: self @ #age + 1'.
	person @ #birthday.
	kunde := Proto new.
	kunde defInheritance: #parent to: person.
	kunde @ #birthday.
	kunde inspect! !

!Proto class methodsFor: 'examples' stamp: 'd.k. 10/22/1998 11:56'!
example3
	"Proto example3"

	|account|
	account := Proto new.
	account defValue: #balance to: 100.
	account defMethod: #deposit: to: ':d | self at: #balance with: self
@ #balance + d'.
	account defMethod: #withdraw: to: ':w | self at: #balance with: (0
max: self @ #balance - w)'.
	account at: #deposit: with: 200.
	account at: #withdraw: with: 50.
	^account @ #balance ! !

!Proto class methodsFor: 'examples' stamp: 'd.k. 10/22/1998 12:08'!
example4
	"Proto example4"

	| account bankAccount stockAccount |
	account := Proto new.
	account defMethod: #deposit: to: ':d | self at: #balance with: self
@ #balance + d'.
	account defMethod: #withdraw: to: ':w | self at: #balance with: (0
max: self @ #balance - w)'.
	bankAccount := Proto new.
	bankAccount defInheritance: #parent to: account.
	bankAccount defValue: #balance to: 100.
	bankAccount at: #deposit: with: 200.
	bankAccount at: #withdraw: with: 50.
	stockAccount := Proto new.
	stockAccount defInheritance: #parent to: account.
	stockAccount defValue: #numShares to: 10.
	stockAccount defValue: #pricePerShare to: 50.0.
	stockAccount defMethod: #balance to: 'self @ #numShares * (self @
#pricePerShare)'.
	stockAccount defMethod: #balance: to: ':b | self at: #numShares
with: b // (self @ #pricePerShare)'.
	stockAccount at: #balance: with: 75.
	^stockAccount @ #balance


! !

Greetings,
Dietmar





More information about the Squeak-dev mailing list