[squeak-dev] The Trunk: Tests-ul.134.mcz

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


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

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

Name: Tests-ul.134
Author: ul
Time: 15 November 2011, 4:23:21.59 am
UUID: f39f56b4-97a3-284c-8859-b96d40ec5391
Ancestors: Tests-nice.133

Integrated BlockLocalTemporariesRemoval from http://bugs.squeak.org/view.php?id=7572 .

=============== Diff against Tests-nice.133 ===============

Item was added:
+ TestCase subclass: #BlockLocalTemporariesRemovalTest
+ 	instanceVariableNames: 'sourceCode'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Tests-Compiler'!
+ 
+ !BlockLocalTemporariesRemovalTest commentStamp: 'ul 11/15/2011 04:22' prior: 0!
+ I test if the parser can remove unused temporaries properly from methods and blocks. I implement several methods to be able to act like a TextEditor.!

Item was added:
+ ----- Method: BlockLocalTemporariesRemovalTest>>assert:isChangedDuringParsingTo:withRemovalOfTemporariesNamed: (in category 'test helper') -----
+ assert: someCode isChangedDuringParsingTo: someOtherCode withRemovalOfTemporariesNamed: someTempNames
+ 
+ 	| failBlock |
+ 	self sourceCode: someCode.
+ 	failBlock := [self fail].
+ 	[self class
+ 			compile: self sourceCode
+ 			classified: nil
+ 			notifying: self
+ 			trailer: self class defaultMethodTrailer
+ 			ifFail: failBlock]
+ 		on: UnusedVariable
+ 		do: [:aNotification | aNotification
+ 				openMenuIn: [:options :emptyCollection :someText | 
+ 					(someTempNames anySatisfy: [:tempName | someText startsWith: tempName])
+ 						ifTrue: [aNotification resume: true]
+ 						ifFalse: [aNotification resume: false]]].
+ 	self assert: self sourceCode = someOtherCode!

Item was added:
+ ----- Method: BlockLocalTemporariesRemovalTest>>correctFrom:to:with: (in category 'requesting') -----
+ correctFrom: start to: stop with: aString
+ 	
+ 	| loc |
+ 	aString = '#insert period' ifTrue:
+ 		[loc := start.
+ 		[(loc := loc-1)>0 and: [(self sourceCode at: loc) isSeparator]]
+ 			whileTrue: [loc := loc-1].
+ 		^ self correctFrom: loc+1 to: loc with: '.'].
+ 	
+ 	self sourceCode: (self sourceCode copyReplaceFrom: start to: stop with: aString)!

Item was added:
+ ----- Method: BlockLocalTemporariesRemovalTest>>deselect (in category 'requesting') -----
+ deselect!

Item was added:
+ ----- Method: BlockLocalTemporariesRemovalTest>>methodWithBlockVariable (in category 'examples') -----
+ methodWithBlockVariable
+ 
+ 	| foo |
+ 	[ | bar | ] value!

Item was added:
+ ----- Method: BlockLocalTemporariesRemovalTest>>nextTokenFrom:direction: (in category 'requesting') -----
+ nextTokenFrom: start direction: dir
+ 	"simple token-finder for compiler automated corrections"
+ 	| loc |
+ 	loc := start + dir.
+ 	[(loc between: 1 and: self sourceCode size) and: [(self sourceCode at: loc) isSeparator]]
+ 		whileTrue: [loc := loc + dir].
+ 	^ loc!

Item was added:
+ ----- Method: BlockLocalTemporariesRemovalTest>>select (in category 'requesting') -----
+ select!

Item was added:
+ ----- Method: BlockLocalTemporariesRemovalTest>>selectFrom:to: (in category 'requesting') -----
+ selectFrom: aPoisition to: anotherPosition!

Item was added:
+ ----- Method: BlockLocalTemporariesRemovalTest>>selectInvisiblyFrom:to: (in category 'requesting') -----
+ selectInvisiblyFrom: userSelection to: last!

Item was added:
+ ----- Method: BlockLocalTemporariesRemovalTest>>selectionInterval (in category 'requesting') -----
+ selectionInterval
+ 
+ 	^ Interval from: 0 to: 0!

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

Item was added:
+ ----- Method: BlockLocalTemporariesRemovalTest>>sourceCode: (in category 'accessing') -----
+ sourceCode: anObject
+ 	sourceCode := anObject!

Item was added:
+ ----- Method: BlockLocalTemporariesRemovalTest>>testBlockTemporaries (in category 'testing') -----
+ testBlockTemporaries
+ 
+ 	| someCode someOtherCode |
+ 	
+ 	someCode := 'test
+ 	| temp |
+ 	[ | foo | ]'.
+ 	someOtherCode := 'test
+ 	| temp |
+ 	[  ]'.
+ 	self assert: someCode isChangedDuringParsingTo: someOtherCode withRemovalOfTemporariesNamed: #('foo').
+ 	
+ 	someCode := 'test
+ 	[ | foo | ]'.
+ 	someOtherCode := 'test
+ 	[  ]'.
+ 	self assert: someCode isChangedDuringParsingTo: someOtherCode withRemovalOfTemporariesNamed: #('foo').
+ 	
+ 	someCode := 'test
+ 	| temp |
+ 	[ | foo | ]'.
+ 	someOtherCode := 'test
+ 	
+ 	[  ]'.
+ 	self assert: someCode isChangedDuringParsingTo: someOtherCode withRemovalOfTemporariesNamed: #('foo' 'temp').!

Item was added:
+ ----- Method: BlockLocalTemporariesRemovalTest>>testComplex (in category 'testing') -----
+ testComplex
+ 
+ 	| someCode someOtherCode |
+ 	
+ 	someCode := 'removeUnusedTemps: methodNode
+ 	"Scan for unused temp names, and prompt the user about the prospect of removing each one found"
+ 
+ 	| madeChanges tempsMarkHolder unusedTempNames tempMarkHoldersToChange encoder requestor|
+ 	encoder := requestor := 1.
+ 	madeChanges := false.
+ 	tempMarkHoldersToChange := OrderedCollection new.
+ 	tempsMarkHolder := self collectTemporaryDeclarationsFrom: methodNode.
+ 	unusedTempNames := encoder unusedTempNames select: 
+ 		[ :temp | (encoder lookupVariable: temp ifAbsent: [ ]) isUndefTemp 
+ 				and: [ UnusedVariable name: temp ]].
+ 	tempsMarkHolder do: [ :currentBlock | ||
+ 		tempMarkHoldersToChange add: currentBlock.
+ 		unusedTempNames do: 
+ 			[ :temp || someAdditionalTemps |
+ 			(self 
+ 				removeUnusedTemporaryNamed: temp 
+ 				from: requestor text asString 
+ 				lookingAt: currentBlock
+ 				movingTempMarksOf: tempMarkHoldersToChange) ifTrue: [ madeChanges := true ]]].
+ 	madeChanges
+ 		ifTrue: [ self removeEmptyTempDeclarationsFrom: methodNode.
+ 			ReparseAfterSourceEditing signal ]'.
+ 	someOtherCode := 'removeUnusedTemps: methodNode
+ 	"Scan for unused temp names, and prompt the user about the prospect of removing each one found"
+ 
+ 	| madeChanges tempsMarkHolder unusedTempNames tempMarkHoldersToChange encoder requestor|
+ 	encoder := requestor := 1.
+ 	madeChanges := false.
+ 	tempMarkHoldersToChange := OrderedCollection new.
+ 	tempsMarkHolder := self collectTemporaryDeclarationsFrom: methodNode.
+ 	unusedTempNames := encoder unusedTempNames select: 
+ 		[ :temp | (encoder lookupVariable: temp ifAbsent: [ ]) isUndefTemp 
+ 				and: [ 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 ]'.
+ 	self assert: someCode isChangedDuringParsingTo: someOtherCode withRemovalOfTemporariesNamed: #('someAdditionalTemps')!

Item was added:
+ ----- Method: BlockLocalTemporariesRemovalTest>>testRegression (in category 'testing') -----
+ testRegression
+ 
+ 	| someCode someOtherCode |
+ 	
+ 	someCode := 'test
+ 	| temp |'.
+ 	someOtherCode := 'test
+ 	'.
+ 	self assert: someCode isChangedDuringParsingTo: someOtherCode withRemovalOfTemporariesNamed: #('temp').
+ 	
+ 	someCode :=  'test
+ 	| temp |'.
+ 	someOtherCode := 'test
+ 	| temp |'.
+ 	self assert: someCode isChangedDuringParsingTo: someOtherCode withRemovalOfTemporariesNamed: #().
+ 	
+ 	someCode :=  'test
+ 	| temp temptemp |'.
+ 	someOtherCode := 'test
+ 	| temp |'.
+ 	self assert: someCode isChangedDuringParsingTo: someOtherCode withRemovalOfTemporariesNamed: #('temptemp').
+ 	!

Item was added:
+ ----- Method: BlockLocalTemporariesRemovalTest>>text (in category 'requesting') -----
+ text
+ 
+ 	^ self sourceCode!




More information about the Squeak-dev mailing list