[HACK] Re: doIfNotNil: -- let's bake the other half

Bert Freudenberg bert at isg.cs.uni-magdeburg.de
Sat Oct 21 12:45:16 UTC 2000


On Fri, 20 Oct 2000, Bob Arning wrote:

> On Fri, 20 Oct 2000 19:36:36 -0400 Doug Way <dway at riskmetrics.com> 
> wrote:
> > Playing devil's advocate, would it be so horrible to just
> > re-use ifNotNil:, but allow zero or one arguments in the block?  
> 
> This is the proposal I would support. I could all be handled by the
> implementation of #value, #value: and their siblings. Some might cry
> that this would hide errors, but I would be happy to live with it.

That'd be cool, indeed. I just tried it - works perfectly! An unfinished
changeset is attached. I changed the compiler to accept a 0-or-1-arg-block
for ifNotNil:, but the actual code generation is not done (it needs to
send value: with an argument). Any compiler freak out there? :)

"Change Set:		valueOpt-bf
Date:			21 October 2000
Author:			Bert Freudenberg

If a block expects less arguments than given, do not fail, but just use
those args. For example:
	(1 to: 3) collect: [OrderedCollection new].
Also makes the ifNotNil:-block take an argument.
UNFINISHED! Compiler accepts 1-arg blocks now, but still need to change
emitters and sizers. Any takers?"

-- Bert
-------------- next part --------------
'From Squeak2.9alpha of 13 June 2000 [latest update: #2774] on 21 October 2000 at 2:39:09 pm'!
"Change Set:		valueOpt-bf
Date:			21 October 2000
Author:			Bert Freudenberg

If a block expects less arguments than given, do not fail, but just use those args. For example:
	(1 to: 3) collect: [OrderedCollection new].
Also makes the ifNotNil:-block take an argument.
UNFINISHED!! Compiler accepts 1-arg blocks now, but still need to change emitters and sizers. Any takers?"!


!ProtoObject methodsFor: 'testing' stamp: 'bf 10/21/2000 14:35'!
ifNil: nilBlock ifNotNil: ifNotNilBlock
	"Evaluate the block, unless I'm == nil (q.v.)"

	^ ifNotNilBlock value: self! !

!ProtoObject methodsFor: 'testing' stamp: 'bf 10/21/2000 14:06'!
ifNotNil: ifNotNilBlock
	"Evaluate the block, unless I'm == nil (q.v.)"

	^ ifNotNilBlock value: self! !

!ProtoObject methodsFor: 'testing' stamp: 'bf 10/21/2000 14:35'!
ifNotNil: ifNotNilBlock ifNil: nilBlock 
	"If I got here, I am not nil, so evaluate the block ifNotNilBlock"

	^ ifNotNilBlock value: self! !


!BlockContext methodsFor: 'evaluating' stamp: 'bf 10/21/2000 13:44'!
valueWithArguments: anArray 
	"Primitive. Evaluate the block represented by the receiver. The argument is an Array whose elements are the arguments for the block. Fail if the length of the Array is less than the number of arguments that the block was expecting. Fail if the block is already being executed. 
	Essential. See Object documentation whatIsAPrimitive."

	<primitive: 82>
	self numArgs = anArray size
		ifTrue: [self error: 'Attempt to evaluate a block that is already being evaluated.']
		ifFalse: [self numArgs < anArray size
			ifTrue: [^ self valueWithArguments: (anArray copyFrom: 1 to: self numArgs)]
			ifFalse: [self error: 'This block requires ' , self numArgs printString , ' arguments.']]! !


!MessageNode methodsFor: 'macro transformations' stamp: 'bf 10/21/2000 14:17'!
transformIfNil: encoder

	(self transformBoolean: encoder) ifFalse: [^ false].
	(MacroSelectors at: special) = #ifNotNil:
	ifTrue:
		[(self checkOptArgBlock: arguments first as: 'ifNotNil arg' from: encoder) ifFalse: [^ false].

		"Transform 'ifNotNil: [stuff]' to 'ifNil: [nil] ifNotNil: [stuff]'.
		Slightly better code and more consistent with decompilation."
		self noteSpecialSelector: #ifNil:ifNotNil:.
		selector _ SelectorNode new key: (MacroSelectors at: special) code: #macro.
		arguments _ {BlockNode withJust: NodeNil. arguments first}.
		(self transform: encoder) ifFalse: [self error: 'compiler logic error'].
		^ true]
	ifFalse:
		[^ self checkBlock: arguments first as: 'ifNil arg' from: encoder]
! !

!MessageNode methodsFor: 'macro transformations' stamp: 'bf 10/21/2000 14:15'!
transformIfNilIfNotNil: encoder
	((self checkBlock: (arguments at: 1) as: 'Nil arg' from: encoder)
		and: [self checkOptArgBlock: (arguments at: 2) as: 'NotNil arg' from: encoder])
		ifTrue: 
			[selector _ SelectorNode new key: #ifTrue:ifFalse: code: #macro.
			receiver _ MessageNode new
				receiver: receiver
				selector: #==
				arguments: (Array with: NodeNil)
				precedence: 2
				from: encoder.
			^true]
		ifFalse: 
			[^false]! !

!MessageNode methodsFor: 'macro transformations' stamp: 'bf 10/21/2000 14:16'!
transformIfNotNilIfNil: encoder
	((self checkOptArgBlock: (arguments at: 1) as: 'NotNil arg' from: encoder)
		and: [self checkBlock: (arguments at: 2) as: 'Nil arg' from: encoder])
		ifTrue: 
			[selector _ SelectorNode new key: #ifTrue:ifFalse: code: #macro.
			receiver _ MessageNode new
				receiver: receiver
				selector: #==
				arguments: (Array with: NodeNil)
				precedence: 2
				from: encoder.
			arguments swap: 1 with: 2.
			^true]
		ifFalse: 
			[^false]! !

!MessageNode methodsFor: 'private' stamp: 'bf 10/21/2000 14:15'!
checkOptArgBlock: node as: nodeName from: encoder
	"Like checkBlock, but allow zero or one args for ifNotNil:"

	node canBeSpecialArgument ifTrue: [^node isMemberOf: BlockNode].
	(node isKindOf: BlockNode)
		ifTrue:	[node numberOfArguments > 1
			ifTrue: [^encoder notify: '<- ', nodeName , ' of ' ,
					(MacroSelectors at: special) , ' must be 0-or-1-argument block']
			ifFalse: [^true]]
		ifFalse: [^encoder notify: '<- ', nodeName , ' of ' ,
					(MacroSelectors at: special) , ' must be a block or variable']! !



More information about the Squeak-dev mailing list