[squeak-dev] The Trunk: Compiler-eem.169.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Aug 18 00:18:13 UTC 2010


Eliot Miranda uploaded a new version of Compiler to project The Trunk:
http://source.squeak.org/trunk/Compiler-eem.169.mcz

==================== Summary ====================

Name: Compiler-eem.169
Author: eem
Time: 17 August 2010, 5:17:57.955 pm
UUID: 527cab12-cb40-42f0-bf0e-3eb940dca528
Ancestors: Compiler-eem.168

Allow the user to choose at what level to delcare an undeclared temp,
either method-level or block-local.

=============== Diff against Compiler-eem.168 ===============

Item was changed:
  VariableNode subclass: #UndeclaredVariableNode
+ 	instanceVariableNames: 'tag'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Compiler-ParseNodes'!

Item was added:
+ ----- Method: Parser>>declareTemp:at: (in category 'error correction') -----
+ declareTemp: name at: levelTag
+ 	"Defer declaring the temp until the parse has completed.  This allows
+ 	 the parser to declare the temp in the minimum enclosing block instead
+ 	 of always at method level.  See Parser>>declareUndeclaredTemps:"
+ 	^(encoder bindUndeclaredTemp: name)
+ 		tag: levelTag;
+ 		yourself!

Item was added:
+ ----- Method: UndeclaredVariableNode>>tag: (in category 'accessing') -----
+ tag: anObject
+ 	"Tag can be whatever one wants it to be; used by Parser to tag
+ 	  undeclared temps with the user's desired declaration level."
+ 
+ 	tag := anObject!

Item was added:
+ ----- Method: UndeclaredVariableNode>>tag (in category 'accessing') -----
+ tag
+ 	"Tag can be whatever one wants it to be; used by Parser to tag
+ 	  undeclared temps with the user's desired declaration level."
+ 
+ 	^tag!

Item was changed:
  ----- Method: Parser>>declareUndeclaredTemps: (in category 'error correction') -----
  declareUndeclaredTemps: methodNode
  	"Declare any undeclared temps, declaring them at the smallest enclosing scope."
  
  	| undeclared userSelection blocksToVars |
  	(undeclared := encoder undeclaredTemps) isEmpty ifTrue:
  		[^self].
  	userSelection := requestor selectionInterval.
  	blocksToVars := IdentityDictionary new.
  	undeclared do:
  		[:var|
  		(blocksToVars
+ 			at: (var tag == #method
+ 					ifTrue: [methodNode block]
+ 					ifFalse: [methodNode accept: (VariableScopeFinder new ofVariable: var)])
- 			at: (methodNode accept: (VariableScopeFinder new ofVariable: var))
  			ifAbsentPut: [SortedCollection new]) add: var name].
  	(blocksToVars removeKey: methodNode block ifAbsent: []) ifNotNil:
  		[:rootVars|
  		rootVars do: [:varName| self pasteTempAtMethodLevel: varName]].
  	(blocksToVars keys sorted: [:a :b| a tempsMark < b tempsMark]) do:
  		[:block| | decl |
  		decl := (blocksToVars at: block) reduce: [:a :b| a, ' ', b].
  		block temporaries isEmpty
  			ifTrue:
  				[self substituteWord: ' | ', decl, ' |'
  					wordInterval: (block tempsMark + 1 to: block tempsMark)
  					offset: requestorOffset]
  			ifFalse:
  				[self substituteWord: decl, ' '
  					wordInterval: (block tempsMark to: block tempsMark - 1)
  					offset: requestorOffset]].
  	requestor selectInvisiblyFrom: userSelection first to: userSelection last + requestorOffset.
  	ReparseAfterSourceEditing signal!

Item was changed:
  ----- Method: UndeclaredVariable>>openMenuIn: (in category 'as yet unclassified') -----
  openMenuIn: aBlock 
  	| alternatives labels actions lines caption choice |
  	alternatives := parser possibleVariablesFor: name.
  	labels := OrderedCollection new.
  	actions := OrderedCollection new.
  	lines := OrderedCollection new.
  	name first isLowercase 
  		ifTrue: 
+ 			[labels add: 'declare method temp'.
+ 			actions add: [parser declareTemp: name at: #method].
+ 			labels add: 'declare block-local temp'.
+ 			actions add: [parser declareTemp: name at: #block].
- 			[labels add: 'declare temp'.
- 			actions add: [parser declareTempAndPaste: name].
  			labels add: 'declare instance'.
  			actions add: [parser declareInstVar: name]]
  		ifFalse: 
  			[labels add: 'define new class'.
  			actions add: [parser defineClass: name].
  			labels add: 'declare global'.
  			actions add: [parser declareGlobal: name].
  			parser canDeclareClassVariable 
  				ifTrue: 
  					[labels add: 'declare class variable'.
  					actions add: [parser declareClassVar: name]]].
  	lines add: labels size.
  	alternatives do: 
  		[:each | 
  		labels add: each.
  		actions add: [parser substituteVariable: each atInterval: interval]].
  	lines add: labels size.
  	labels add: 'cancel'.
  	caption := 'Unknown variable: ' , name , ' please correct, or cancel:'.
  	choice := aBlock value: labels value: lines value: caption.
  	self resume: (actions at: choice ifAbsent: [nil])!




More information about the Squeak-dev mailing list