Metaclass fun

Travis Griggs tgriggs at keyww.com
Tue Apr 21 05:26:40 UTC 1998


My colleague and I were sitting around this afternoon discussing the
name of a method that had quite a few arguments. What it really revolved
around was the ordering of the argument list in a rather generalized
utility API we had envisioned. We couldn't agree on whether it should be
a:b:c: or c:a:b:, etc, trying to make it sound as natural language as
possible. Having run across this before, I said "to heck with it, let's
solve this problem once and for all". The fix took five minutes to
implement and test, resulting in 3 methods. I did it in VW becuase that
was running at the time. I then fired up Squeak and had it running there
in a minute.

The approach is to basically intercept doesNotUnderstand: and then send
a message called attemptToUnderstand: which basically attempts to find a
reordered keyword message signature that matches, and if so, resend the
correct message with the arguments reordered.

I love Smalltalk - it's so cool. Three methods and five minutes and I've

made keyword ordering irrelavent. How's that for changing the language
in a short amount of time? The blue book section on keywords can now
read (paraphrased) something like this:

"...There are three kinds of messages in Squeak: unary, binary, and
keyword. Unary messages are evaluated before binary ones, and binary
ones before keyword ones. {Blah blah blah about unary and binary
messages}. Keyword messages are denoted by a list of arguments and
argument keywords.The syntax for each keyword/argument pair is keyword
followed by a colon and then the argument statement: e.g. "keyword:
argument".  The ordering of argument/keyword pairs is arbitrary for any
message send. When implementing a keyword message you may code the
message selector in whatever order suites your fancy..."

What would be really cool would be to cause the code to "grow" so that
each time it ran across this, it made a copy of the compiled method,
reindexed the argument accesses in the byte codes, and then placed it in
the method dictionary under the new signature. Don't even think it would
require "compiler" support. :) I'll leave this to the interested
student, or until the performance hit from the above bites me. :) This
whole notion of "growing" code has fascinated me ever since Alan talked
about it at OOPSLA and I keep looking for an excuse to use it.

The attachment adds an additional message for Symbol and an additional
message for Object. It also changes doesNotUnderstand: in Object, so if
you've made your own changes there, you'll want to integrate the effect.
It also adds conforms: to Collection (allthough I could've used
includesAll:).

--
Travis Griggs
Key Technology
tgriggs at keyww.com
To Smalltalk! - and Beyond!



'From Squeak 1.31 of Feb 4, 1998 on 20 April 1998 at 2:34:17 pm'!

!Object methodsFor: 'error handling'!
attemptToUnderstand: aMessage 
	"go and see if we can find a keyword selector whose keys are the same but in different order, if we can then reorder the arguments appropriately and resend the reordered selector and arguments - returns the argument when resolution is not possible"

	"the very first thing we do is find out whether this even makes sense and eliminate wasted cycles trying to correct a condition that can't be corrected, that where there's not more than one keyword"

	| oldSel oldArgs oldKeys newSel newArgs newKeys |
	(oldArgs := aMessage arguments) size <= 1 ifTrue: [^aMessage].
	oldSel := aMessage selector.
	oldKeys := oldSel keywords.
	(newSel := self class allSelectors 
				detect: [:eachAltSel | eachAltSel sameKeywords: oldKeys]
				ifNone: [nil]) isNil 
		ifTrue: [^aMessage].
	newKeys := newSel keywords.
	newArgs := Array new: oldArgs size.	"the common case is probably a 2 key inversion, in this case, it's just a transposition of the argument array, and we can save a bit of time avoiding indexing"
	newArgs size = 2 
		ifTrue: 
			[newArgs
				at: 1 put: (oldArgs at: 2);
				at: 2 put: (oldArgs at: 1)]
		ifFalse: 
			[newKeys keysAndValuesDo: 
					[:index :keyword | 
					newArgs at: index put: (oldArgs at: (oldKeys indexOf: keyword))]].
	^self perform: newSel withArguments: newArgs! !

!Object methodsFor: 'error handling' stamp: 'TAG 4/20/98 14:33'!
doesNotUnderstand: aMessage 
	 "Handle the fact that there was an attempt to send the given message to the receiver but the receiver does not understand this message (typically sent from the machine when a message is sent to the receiver and no method is defined for that selector)."
	"Unless the receiver has an error handler defined for the active process, report to the user that the receiver does not understand the argument, aMessage, as a message."
	"Testing: (3 activeProcess)"

	| handler errorString result |
	(Preferences autoAccessors and: [self tryToDefineVariableAccess: aMessage])
		ifTrue: [^ aMessage sentTo: self].
	(result _ self attemptToUnderstand: aMessage) == aMessage ifFalse: [^result].
	errorString _ 'Message not understood: ', aMessage selector.
	(handler _ Processor activeProcess errorHandler) notNil
		ifTrue: [handler value: errorString value: self]
		ifFalse: [DebuggerView openContext: thisContext
					label: errorString
					contents: thisContext shortStack].
	^ aMessage sentTo: self! !


!Symbol methodsFor: 'system primitives'!
sameKeywords: aCollectionOfKeywords 
	"return whether the reciever represents the equivalent set of keywords, regardless of order"

	^self numArgs = aCollectionOfKeywords size 
		and: [self keywords conforms: [:each | aCollectionOfKeywords includes: each]]! !





More information about the Squeak-dev mailing list