Defining temporary variables in blocks

Alan Lovejoy sourcery at pacbell.net
Mon Jul 5 03:34:37 UTC 1999


I am publishing a "fix" (as I see it, anyway) to Squeak so that
temporary variables can be declared in blocks.  I don't know
whether other such file-ins that do the same thing may be
available or not, but this one is relatively simple and straightforward.

The file-in is included as an attachment.

--Alan

'From Squeak 2.4b of April 23, 1999 on 26 June 1999 at 2:27:13 pm'!

'Step 0: Miscellaneous fixes: These were motivated by problems I 
encountered that
had nothing whatsoever to do with adding support for block temps.  In 
other words,
these fixes are NOT REQUIRED by the enhancement for block temporaries.'!

!Character methodsFor: 'accessing' stamp: 'ALL 6/26/1999 13:16'!
value
	"Answer the value of the receiver that represents its ascii encoding."

	^value! !

!Debugger methodsFor: 'private' stamp: 'ALL 6/26/1999 13:25'!
resumeProcess: aTopView
	Smalltalk isMorphic ifFalse: [aTopView == nil ifFalse: 
[aTopView erase]].
	interruptedProcess suspendedContext method
			== (Process compiledMethodAt: #terminate) ifFalse:
		[contextStackIndex > 1
			ifTrue: [interruptedProcess popTo: self 
selectedContext]
			ifFalse: [interruptedProcess install: self 
selectedContext].
		Smalltalk isMorphic
			ifTrue: [Project current resumeProcess: 
interruptedProcess]
			ifFalse: [ScheduledControllers
 
	activeControllerNoTerminate: interruptedController
						andProcess: 
interruptedProcess]].
	"if old process was terminated, just terminate current one"
	interruptedProcess _ nil. "Before delete, so release doesn't 
terminate it"
	Smalltalk isMorphic
		ifTrue: [aTopView delete. World displayWorld]
		ifFalse: [aTopView controller closeAndUnscheduleNoErase].
	Smalltalk installLowSpaceWatcher.  "restart low space handler"
	Processor terminateActive
! !

!Model methodsFor: 'dependents' stamp: 'ALL 6/26/1999 13:29'!
topView
	"Find the first top view on me. Is there any danger of their 
being two with the same model?  Any danger from ungarbage collected 
old views?  Ask if schedulled?"

	dependents ifNil: [^ nil].
	World ifNotNil: [
		dependents do:
			[:v | ((v isKindOf: SystemWindow) and: [v 
isInWorld]) ifTrue: [^ v]].
		^ nil].
	dependents do: [:v | (v isMorph ifTrue: [v] ifFalse: [v 
superView]) ifNil: [v model == self ifTrue: [^ v]]].
	^ nil
! !

'Add blockTemps: '!
'Step 1: Redefined classes'!


ParseNode subclass: #Encoder
	instanceVariableNames: 'scopeTable nTemps supered requestor 
class literalStream selectorSet litIndSet litSet sourceRanges 
allTempNodes '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'System-Compiler'!

Scanner subclass: #Parser
	instanceVariableNames: 'here hereType hereMark prevToken 
prevMark encoder requestor parseNode failBlock requestorOffset 
tempsMark temporaryVariables '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'System-Compiler'!

'Add blockTemps: '!
'Step 2: Ensure that instance variables are properly initialized'!

!Encoder methodsFor: 'initialize-release'!
initialize
	allTempNodes _ OrderedCollection new.! !

!Encoder class methodsFor: 'instance creation'!
new
	^super new initialize! !

!Parser methodsFor: 'initialize'!
initialize
	temporaryVariables _ OrderedCollection new! !


!Parser class methodsFor: 'instance creation'!
new
	^super new initialize! !

'Add blockTemps: '!
'Step 3: Enhance Encoder to support block temps'!

!Encoder methodsFor: 'private'!
reallyBind: name

	| node |
	node _ self newTemp: name.
	allTempNodes add: node.
	scopeTable at: name put: node.
	^node! !


!Encoder methodsFor: 'temps'!
bindBlockTemp: name
	"Declare a block temporary; error not if a field or class variable."
	| node |
	node _ scopeTable
			at: name
			ifAbsent: [^self reallyBind: name].
	node isTemp
		ifTrue: [node scope >= 0 ifTrue:
					[^ self notify: 'Name already 
used in this method'].
				node scope: 0]
		ifFalse: [^ self notify: 'Name already used in this class'].
	^node
! !

!Encoder methodsFor: 'encoding'!
encodeVariable: name ifUnknown: action
	| varNode |
	varNode _
		scopeTable
			at: name
			ifAbsent:
				[self lookupInPools: name
					ifFound: [:assoc | ^self 
global: assoc name: name].
				^action value].
	(varNode isTemp and:[varNode scope <0]) ifTrue: [^ self 
notify: 'Name ', name printString, ' already used in this method, 
perhaps as block temp'].
	^varNode! !


!Encoder methodsFor: 'temps'!
bindTemps: anOrderedCollection
	"Bind the strings in the arg into VariableNodes. Answer the 
resulting collection"

	^anOrderedCollection collect: [:string | self bindTemp: string]! !

'Add blockTemps: '!
'Step 4: Enhance Parser to support block temps'!

!Parser methodsFor: 'expression types'!
temporaryNames
	"Parse [ '|' (variable)* '|' ] to build a list of declared temp names"
	| names |
	(self match: #verticalBar) ifFalse:	"no temps"
		[tempsMark _ hereMark.
		^ #()].
	names _ OrderedCollection new.
	[hereType == #word]
		whileTrue: [names addLast:  self advance].
	(self match: #verticalBar) ifTrue:
		[tempsMark _ prevMark.
		^ names].
	^self expected: 'Vertical bar'! !

!Parser methodsFor: 'expression types'!
temporaries
	temporaryVariables addAll: (self temporaryNames collect: 
[:string | encoder bindTemp: string])! !

!Parser methodsFor: 'expression types'!
blockTemporaries
	"Copy of #temporaries, except we do not track tempsMark"
	| vars |
	(self match: #verticalBar) ifFalse:	"no temps"
		[^ #()].
	vars _ OrderedCollection new.
	[hereType == #word]
		whileTrue: [vars addLast: (encoder bindBlockTemp: 
self advance)].
	(self match: #verticalBar) ifTrue:
		[^ vars].
	^self expected: 'Vertical bar'! !

!Parser methodsFor: 'expression types'!
blockExpression
	" [ {:var} ( | statements) ] => BlockNode."

	| argNodes blockTemps|
	argNodes _ OrderedCollection new.
	[self match: #colon
	"gather any arguments"]
		whileTrue:
			[argNodes addLast: (encoder autoBind: self 
argumentName)].
	(argNodes size > 0 & (hereType ~~ #rightBracket) and: [(self 
match: #verticalBar) not])
		ifTrue: [^self expected: 'Vertical bar'].
	blockTemps _ self blockTemporaries.
	self statements: argNodes innerBlock: true.
	(self match: #rightBracket)
		ifFalse: [^self expected: 'Period or right bracket'].
	"Scope of args and block temps no longer active"
	blockTemps do:[:arg| arg scope: -1].
	argNodes do: [:arg | arg scope: -1] ! !

!Parser methodsFor: 'expression types' stamp: 'ALL 6/26/1999 14:25'!
method: doit context: ctxt
	" pattern [ | temporaries ] block => MethodNode."

	| sap blk prim temps messageComment methodNode tempNames |
	sap _ self pattern: doit inContext: ctxt.
	"sap={selector, arguments, precedence}"
	(sap at: 2) do: [:argNode | argNode isArg: true].
	tempNames _ self temporaryNames.
	temps _ OrderedCollection new.
	messageComment _ currentComment.
	currentComment _ nil.
	tempNames do:[:nm|
		temps add: (encoder bindTemp: nm)].
	prim _ doit ifTrue: [0] ifFalse: [self primitive].
	self statements: #() innerBlock: doit.
	blk _ parseNode.
	doit ifTrue: [blk returnLast]
		ifFalse: [blk returnSelfIfNoOther].
	hereType == #doIt ifFalse: [^self expected: 'Nothing more'].
	self interactive ifTrue: [self removeUnusedTemps].
	methodNode _ MethodNode new comment: messageComment.
	^methodNode
		selector: (sap at: 1)
		arguments: (sap at: 2)
		precedence: (sap at: 3)
		temporaries: temps
		block: blk
		encoder: encoder
		primitive: prim! !



Content-Type: text/x-vcard; charset=us-ascii;
  name="sourcery.vcf"
Content-Transfer-Encoding: 7bit
Content-Description: Card for Alan Lovejoy
Content-Disposition: attachment;
  filename="sourcery.vcf"

Attachment converted: Anon:sourcery.vcf 9 (TEXT/R*ch) (0000ADB4)





More information about the Squeak-dev mailing list