[ENH] Re: Tuples

Bert Freudenberg bert at isgnw.CS.Uni-Magdeburg.De
Thu Jan 20 15:41:33 UTC 2000


On Wed, 19 Jan 2000, Vassili Bykov wrote:

> Source code is less important than you think. :-)
> 
> Attached is an implementation of Tuple as suggested by Dan.  It may be rough
> and hacky in places (CompiledMethod class>>toSetField: for example) and
> lacks some useful instance-side behaviour  but it seems to work in 2.7.  It
> does prove the concept anyway.
> 
> Here is the skinny: you evaluate something like
> 
>   ^ Tuple voltage: 220 current: 7.5 startingTorque: 185
> 
> If code like that has never been evaluated before, Tuple creates an
> anonymous subclass of itself with instance variables 'voltage', 'current',
> and 'startingTorque'.  (The subclass is saved keyed by the creation message
> selector so if another tuple is created later using same message, the class
> is reused).  The subclass is anonymous in the sense it is not registered
> with the system dictionary; the only object holding onto it is the tuple
> class registry in Tuple.  An instance of the class is created and
> initialized according to the message arguments.  The class' method
> dictionary contains six methods: three getters (#voltage, #current,
> #startingTorque) and three setters (#voltage:, #current:, #startingTorque:).
> The methods are created "by hand", they have no source and what's most fun,
> they are shared between tuple classes.  For example, there is just one
> method that fetches the first instance variable from a tuple.  All tuple
> classes hold that method under different selectors in their method
> dictionaries to retrieve their first elements.  Because tuple classes are
> real classes, with instance variable names and all, inspectors work fine on
> tuples.
> 
> Note that the two expressions
> 
> 	Tuple first: 1 second: 2
> 	Tuple second: 'two' first: 'one'
> 
> would use two different tuple classes.  This could be optimized.  It would
> be fairly easy to somehow normalize the tuple element set before using it as
> a cache key.  On the bright side, the behaviour of both tuples is the same
> anyway.
> 
> Enjoy.

Vassili - this is great! The idea of hidden and partly shared classes does
make the whole concept really usefull. I attached a little enhancement so
Tuples can be stored and printed correctly.

  -Bert-
-------------- next part --------------
'From Squeak2.7 of 5 January 2000 [latest update: #1780] on 19 January 2000 at 9:27:54 pm'!
Object subclass: #Tuple
	instanceVariableNames: ''
	classVariableNames: 'GetterCache SetterCache TupleClasses '
	poolDictionaries: ''
	category: 'Kernel-Objects'!

!CompiledMethod class methodsFor: 'instance creation' stamp: 'VB 1/19/2000 20:49'!
toSetField: field 
	"Answer an instance of me that sets the instance variable 
	indexed by the argument, field."

	| byteCount method base |
	byteCount _ field < 8 ifTrue: [3] ifFalse: [4].
	method _ self newBytes: byteCount nArgs: 1 nTemps: 0 nStack: 1 nLits: 0 primitive: 0.
	base _ method initialPC.
	method at: base put: 16r10. "pushTemp: 0"
	byteCount = 3
		ifTrue: [method at: base + 1 put: 16r60 + field] "popIntoRecvr: field"
		ifFalse: [method 
			at: base + 1 put: 16r82; "popIntoRcvr:"
			at: base + 2 put: field].
	method at: base + byteCount - 1 put: 16r78. "returnSelf"
	^method
! !


!Tuple commentStamp: 'VB 1/19/2000 21:27' prior: 0!
I am an implementation of a generic Tuple by Vassili Bykov <vassili at objectpeople.com>.

If you evaluate something like

  ^ Tuple voltage: 220 current: 7.5 startingTorque: 185

and if code like that has never been evaluated before, Tuple creates an anonymous subclass of itself with instance variables 'voltage', 'current', and 'startingTorque'.  (The subclass is saved keyed by the creation message selector so if another tuple is created later using #voltage:current:startingTorque: message, the class is reused).  The subclass is anonymous in the sense it is not registered with the system dictionary; the only object holding onto it is the tuple class registry in Tuple.  An instance of the class is created and initialized according to the message arguments.  The class' method dictionary contains six methods: three getters (#voltage, #current, #startingTorque) and three setters (#voltage:, #current:, #startingTorque:). The methods are created "by hand", they have no source and what's most fun, they are shared between tuple classes.  For example, there is just one method that fetches the first instance variable from a tuple.  All tuple classes hold that method under different selectors in their method dictionaries to retrieve their first elements.  Because tuple classes are real classes, with instance variable names and all, inspectors work fine on tuples.

!


!Tuple class methodsFor: 'class initialization' stamp: 'VB 1/19/2000 20:16'!
initialize
	"Tuple initialize"

	TupleClasses _ Dictionary new.
	GetterCache _ Dictionary new.
	SetterCache _ Dictionary new! !

!Tuple class methodsFor: 'instance creation' stamp: 'VB 1/19/2000 20:58'!
doesNotUnderstand: aMessage

	| selector |
	selector _ aMessage selector.
	selector isKeyword ifFalse: [^super doesNotUnderstand: aMessage].
	^(TupleClasses
		at: selector
		ifAbsentPut: [self createTupleClassFor: selector]) 
			newWith: aMessage arguments! !

!Tuple class methodsFor: 'instance creation' stamp: 'VB 1/19/2000 20:53'!
newWith: anArray

	| instance |
	instance := self new.
	anArray withIndexDo:
		[:object :index |
		instance instVarAt: index put: object].
	^instance! !

!Tuple class methodsFor: 'private' stamp: 'VB 1/19/2000 20:09'!
createTupleClassFor: aSelector

	| instVarNames newClass |
	instVarNames _ aSelector keywords 
		collect: [:each | each copyFrom: 1 to: each size - 1].
	newClass _ ClassBuilder new
		newSubclassOf: self
		type: #normal
		instanceVariables: instVarNames
		from: nil
		unsafe: true.
	self
		linkMethodsInto: newClass
		withVariables: instVarNames.
	^newClass! !

!Tuple class methodsFor: 'private' stamp: 'VB 1/19/2000 20:16'!
getterFor: anIndex

	^GetterCache
		at: anIndex
		ifAbsentPut: [CompiledMethod toReturnField: anIndex]! !

!Tuple class methodsFor: 'private' stamp: 'VB 1/19/2000 20:51'!
linkMethodsInto: newClass withVariables: variableNames

	(0 to: variableNames size - 1)
		with: variableNames
		do: [:index :varName |
			newClass
				addSelector: varName asSymbol
					withMethod: (self getterFor: index);
				addSelector: (varName, ':') asSymbol
					withMethod: (self setterFor: index)]! !

!Tuple class methodsFor: 'private' stamp: 'VB 1/19/2000 20:20'!
setterFor: anIndex

	^SetterCache
		at: anIndex
		ifAbsentPut: [CompiledMethod toSetField: anIndex]! !


Tuple removeSelector: #elements!
Tuple initialize!
-------------- next part --------------
'From Squeak2.7 of 5 January 2000 [latest update: #1782] on 20 January 2000 at 4:38:55 pm'!
"Change Set:		Tuples-bf
Date:			20 January 2000
Author:			Bert Freudenberg

Store and print Vassili's Tuples"!


!Tuple methodsFor: 'printing' stamp: 'bf 1/20/2000 16:36'!
printOn: aStream
	self class == Tuple ifTrue: [^super printOn: aStream].
	aStream nextPutAll: 'Tuple('.
	self class instVarNames
		do: [:var | aStream nextPutAll: var; nextPut: $=; print: (self instVarNamed: var)]
		separatedBy: [aStream space].
	aStream nextPut: $)! !

!Tuple methodsFor: 'printing' stamp: 'bf 1/20/2000 16:35'!
storeOn: aStream
	self class == Tuple ifTrue: [^super storeOn: aStream].
	aStream nextPutAll: '(Tuple '.
	self class instVarNames
		do: [:var | aStream nextPutAll: var; nextPutAll: ': '; store: (self instVarNamed: var)]
		separatedBy: [aStream space].
	aStream nextPut: $)
! !


!Tuple class methodsFor: 'organization' stamp: 'bf 1/20/2000 16:20'!
name
	self == Tuple ifTrue: [^super name].
	^self instVarNames inject: 'Tuple' into: [:nm :var | nm, var capitalized]! !




More information about the Squeak-dev mailing list