[squeak-dev] The Trunk: Compiler-ul.220.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Nov 15 03:35:59 UTC 2011


Levente Uzonyi uploaded a new version of Compiler to project The Trunk:
http://source.squeak.org/trunk/Compiler-ul.220.mcz

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

Name: Compiler-ul.220
Author: ul
Time: 15 November 2011, 4:25:41.558 am
UUID: 1afd47cf-c700-2f43-a87b-e46ee1bcba39
Ancestors: Compiler-nice.219

Integrated the Parser changes from http://bugs.squeak.org/view.php?id=7572 :

Change Set:		parser-lw
Date:			31 May 2011
Author:			Lars Wassermann

Changed the Parser to
	remove Block Local Temporaries
	ask even if there are no method local temporaries
	don't ask several times for removal
	don't recommend to remove temporaries which are assigned to

=============== Diff against Compiler-nice.219 ===============

Item was changed:
  Scanner subclass: #Parser
+ 	instanceVariableNames: 'here hereType hereMark hereEnd prevMark prevEnd encoder requestor parseNode failBlock requestorOffset tempsMark doitFlag properties category queriedUnusedTemporaries'
- 	instanceVariableNames: 'here hereType hereMark hereEnd prevMark prevEnd encoder requestor parseNode failBlock requestorOffset tempsMark doitFlag properties category'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Compiler-Kernel'!
  
  !Parser commentStamp: '<historical>' prior: 0!
  I parse Smalltalk syntax and create a MethodNode that is the root of the parse tree. I look one token ahead.!

Item was added:
+ ----- Method: Parser>>collectTemporaryDeclarationsFrom: (in category 'error correction') -----
+ collectTemporaryDeclarationsFrom: methodNode
+ 	| tempsMarks str |
+ 	tempsMarks := OrderedCollection new.
+ 	str := requestor text asString.
+ 	methodNode accept: (ParseNodeEnumerator
+ 		ofBlock: [ :aNode | 
+ 			| mark |
+ 			(aNode class canUnderstand: #tempsMark) 
+ 				ifTrue: 
+ 					[mark := aNode tempsMark.
+ 					(mark notNil and: [ mark between: 1 and: str size ] and: [ (str at: mark) = $| ])
+ 						ifTrue: [ tempsMarks addLast: aNode ]]]).
+ 	(tempsMark notNil and: [ tempsMark between: 1 and: str size ] and: [ (str at: tempsMark) = $| ])
+ 						ifTrue: [ tempsMarks addLast: self ].
+ 	^ tempsMarks sorted: [ :a :b | a tempsMark > b tempsMark ]!

Item was changed:
  ----- Method: Parser>>method:context: (in category 'expression types') -----
  method: doit context: ctxt 
  	" pattern [ | temporaries ] block => MethodNode."
  
  	| sap blk prim temps messageComment methodNode |
  	sap := self pattern: doit inContext: ctxt.
  	"sap={selector, arguments, precedence}"
  	self properties selector: (sap at: 1).
  	encoder selector: (sap at: 1).
  	(sap at: 2) do: [:argNode | argNode beMethodArg].
  	doit ifFalse: [self pragmaSequence].
  	temps := self temporaries.
  	messageComment := currentComment.
  	currentComment := nil.
  	doit ifFalse: [self pragmaSequence].
  	prim := self pragmaPrimitives.
  	self statements: #() innerBlock: doit.
  	blk := parseNode.
  	doit ifTrue: [blk returnLast]
  		ifFalse: [blk returnSelfIfNoOther: encoder].
  	hereType == #doIt ifFalse: [^self expected: 'Nothing more'].
  	methodNode := self newMethodNode comment: messageComment.
  	methodNode
  		selector: (sap at: 1)
  		arguments: (sap at: 2)
  		precedence: (sap at: 3)
  		temporaries: temps
  		block: blk
  		encoder: encoder
  		primitive: prim
  		properties: properties.
  	self interactive ifTrue:
  		[self declareUndeclaredTemps: methodNode.
+ 		 self removeUnusedTemps: methodNode].
- 		 self removeUnusedTemps].
  	^methodNode!

Item was added:
+ ----- Method: Parser>>queriedUnusedTemporaries (in category 'accessing') -----
+ queriedUnusedTemporaries
+ 
+ 	queriedUnusedTemporaries ifNil: 
+ 		[queriedUnusedTemporaries := Dictionary new].
+ 	^queriedUnusedTemporaries!

Item was added:
+ ----- Method: Parser>>removeEmptyTempDeclarationsFrom: (in category 'error correction') -----
+ removeEmptyTempDeclarationsFrom: methodNode
+ 
+ 	| sourceCode madeChanges tempsMarkHolder |
+ 	sourceCode := requestor text asString.
+ 	tempsMarkHolder := self collectTemporaryDeclarationsFrom: methodNode.
+ 	madeChanges := false.
+ 	tempsMarkHolder do: [ :currentBlock | | tempsMarkChar0 tempsMarkChar1 tempsMarkChar2 end start |
+ 		tempsMarkChar0 := (sourceCode at: currentBlock tempsMark).
+ 		tempsMarkChar1 := (sourceCode at: currentBlock tempsMark - 1).
+ 		tempsMarkChar2 := (sourceCode at: currentBlock tempsMark - 2).
+ 		tempsMarkChar0 = $| & tempsMarkChar1 = $| 
+ 			ifTrue: 
+ 				[ end := currentBlock tempsMark. 
+ 				start := end - 1].
+ 		tempsMarkChar0 = $| & tempsMarkChar1 = $  & tempsMarkChar2 = $| 
+ 			ifTrue: 
+ 				[ end := currentBlock tempsMark. 
+ 				start := end - 2].
+ 		
+ 		start notNil & end notNil 
+ 			ifTrue: 
+ 				[requestor correctFrom: start to: end with: ''.
+ 				madeChanges := true.
+ 				currentBlock tempsMark: nil]].
+ 	madeChanges ifTrue: [ReparseAfterSourceEditing signal]!

Item was added:
+ ----- Method: Parser>>removeUnusedTemporaryNamed:from:lookingAt:movingTempMarksOf: (in category 'error correction') -----
+ removeUnusedTemporaryNamed: temp from: str lookingAt: currentBlock movingTempMarksOf: someBlocks
+ 
+ 	| start end |
+ 	end := currentBlock tempsMark - 1.
+ 	["Beginning at right temp marker..."
+ 	start := end - temp size + 1.
+ 	end < temp size or: [ (str at: start) = $| ]
+ 		or: [ temp = (str copyFrom: start to: end) 
+ 			and: [ ((str at: start - 1) = $| | (str at: start - 1) isSeparator) 
+ 				& ((str at: end + 1) = $| | (str at: end + 1) isSeparator) ] ]]
+ 		whileFalse: [ 
+ 			"Search left for the unused temp"
+ 			end := requestor nextTokenFrom: end direction: -1 ].
+ 	(end < temp size or: [ (str at: start) = $| ])
+ 		ifFalse: 
+ 			[(str at: start - 1) = $ 
+ 				ifTrue: [ start := start - 1 ].
+ 			requestor correctFrom: start to: end with: ''.
+ 			someBlocks do: [ :aBlock | aBlock tempsMark: aBlock tempsMark - (end - start + 1)].
+ 			^true ].
+ 	^false!

Item was removed:
- ----- Method: Parser>>removeUnusedTemps (in category 'error correction') -----
- removeUnusedTemps
- 	"Scan for unused temp names, and prompt the user about the prospect of removing each one found"
- 
- 	| str madeChanges | 
- 	madeChanges := false.
- 	str := requestor text asString.
- 	((tempsMark between: 1 and: str size)
- 		and: [(str at: tempsMark) = $|]) ifFalse: [^ self].
- 	encoder unusedTempNames do:
- 		[:temp | | start end |
- 		(UnusedVariable name: temp) ifTrue:
- 			[(encoder lookupVariable: temp ifAbsent: []) isUndefTemp
- 				ifTrue:
- 					[end := tempsMark.
- 					["Beginning at right temp marker..."
- 					start := end - temp size + 1.
- 					end < temp size or: [temp = (str copyFrom: start to: end)
- 							and: [(str at: start-1) isSeparator & (str at: end+1) isSeparator]]]
- 						whileFalse:
- 							["Search left for the unused temp"
- 							end := requestor nextTokenFrom: end direction: -1].
- 					end < temp size ifFalse:
- 						[(str at: start-1) = $  ifTrue: [start := start-1].
- 						requestor correctFrom: start to: end with: ''.
- 						str := str copyReplaceFrom: start to: end with: ''. 
- 						madeChanges := true.
- 						tempsMark := tempsMark - (end-start+1)]]
- 				ifFalse:
- 					[self inform:
- 'You''ll first have to remove the\statement where it''s stored into' withCRs]]].
- 	madeChanges ifTrue: [ReparseAfterSourceEditing signal]!

Item was added:
+ ----- Method: Parser>>removeUnusedTemps: (in category 'error correction') -----
+ removeUnusedTemps: methodNode
+ 	"Scan for unused temp names, and prompt the user about the prospect of removing each one found"
+ 
+ 	| madeChanges tempsMarkHolder unusedTempNames tempMarkHoldersToChange |
+ 	madeChanges := false.
+ 	tempMarkHoldersToChange := OrderedCollection new.
+ 	tempsMarkHolder := self collectTemporaryDeclarationsFrom: methodNode.
+ 	unusedTempNames := encoder unusedTempNames select: 
+ 		[ :temp | (encoder lookupVariable: temp ifAbsent: [ ]) isUndefTemp 
+ 				and: [ self queriedUnusedTemporaries at: temp ifAbsentPut: [UnusedVariable name: temp] ]].
+ 	tempsMarkHolder do: [ :currentBlock | 
+ 		tempMarkHoldersToChange add: currentBlock.
+ 		unusedTempNames do: 
+ 			[ :temp |
+ 			(self 
+ 				removeUnusedTemporaryNamed: temp 
+ 				from: requestor text asString 
+ 				lookingAt: currentBlock
+ 				movingTempMarksOf: tempMarkHoldersToChange) ifTrue: [ madeChanges := true ]]].
+ 	madeChanges
+ 		ifTrue: [ self removeEmptyTempDeclarationsFrom: methodNode.
+ 			ReparseAfterSourceEditing signal ]!

Item was added:
+ ----- Method: Parser>>tempsMark (in category 'accessing') -----
+ tempsMark
+ 	^ tempsMark!

Item was added:
+ ----- Method: Parser>>tempsMark: (in category 'accessing') -----
+ tempsMark: aNumber
+ tempsMark := aNumber!




More information about the Squeak-dev mailing list