[Pkg] The Trunk: Tests-nice.253.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Sep 20 19:47:22 UTC 2013


Nicolas Cellier uploaded a new version of Tests to project The Trunk:
http://source.squeak.org/trunk/Tests-nice.253.mcz

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

Name: Tests-nice.253
Author: nice
Time: 20 September 2013, 9:46:53.846 pm
UUID: d1fa080c-74c8-421c-baff-e6c0b87b119c
Ancestors: Tests-nice.252

Don't pass a category to a Compiler, classifying is not its job.
Also, avoid passing a nil context, that sounds superfluous.

=============== Diff against Tests-nice.252 ===============

Item was changed:
  ----- 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 changed:
  ----- Method: ClosureCompilerTest>>testBlockDoitDecompilation (in category 'tests') -----
  testBlockDoitDecompilation
  	"Tests that decompile of a doit block with remote vars executes correcly"
  	"Tests that decompilation of a Block, when 'method' of block is equivalent to that compiled by a DoIt, preserves the temp names "
  	
  	|blockSourceStream methodNode compiledMethod block decompiledBlock|
  	blockSourceStream := '|x y| [:a :b | x := a. y := b. x + y]' readStream.
  	methodNode := nil class evaluatorClass new 
+ 			compileNoPattern: blockSourceStream in: nil class notifying: nil ifFail: [nil]..
- 			compileNoPattern: blockSourceStream in: nil class context: nil notifying: nil ifFail: [nil]..
  	compiledMethod := methodNode generateWithTempNames.
  	block := nil withArgs: #() executeMethod: compiledMethod.
  	
  	self shouldnt: [decompiledBlock := block decompile] raise: Error.
  	self assert: '{[:a :b | 
  x := a.
  	y := b.
  	x + y]}' equals: decompiledBlock printString
  !

Item was changed:
  ----- Method: ClosureCompilerTest>>testDecompiledDoitMethodTempNames (in category 'tests') -----
  testDecompiledDoitMethodTempNames
  	"self new testDecompiledDoitMethodTempNames"
  	"Test that a decompiled doit that has been copied with temps decompiles to the input"
  	| removeComments |
  	removeComments := [:n| n comment: nil].
  	self closureCases do:
  		[:source| | mns m mps mnps |
  		"Need to compare an ungenerated tree with the generated method's methodNode
  		 because generating code alters the tree when it introduces remote temp vectors."
  		mns := #(first last) collect:
  					[:ignored|
  					source first isLetter
  						ifTrue:
  							[self class newCompiler
  								compile: source
  								in: self class
  								notifying: nil
  								ifFail: [self error: 'compilation error']]
  						ifFalse:
  							[self class newCompiler
  								compileNoPattern: source
  								in: self class
- 								context: nil
  								notifying: nil
  								ifFail: [self error: 'compilation error']]].
  		m := (mns last generateWithTempNames).
  		removeComments value: mns first.
  		mns first nodesDo: removeComments.
  		self assert: (mnps := mns first printString) = (mps := m methodNode printString)]!

Item was changed:
  ----- Method: ClosureCompilerTest>>testMethodAndNodeTempNames (in category 'tests') -----
  testMethodAndNodeTempNames
  	"self new testMethodAndNodeTempNames"
  	"Test that BytecodeAgnosticMethodNode>>blockExtentsToTempRefs answers the same
  	 structure as CompiledMethod>>blockExtentsToTempRefs when the method has been
  	 copied with the appropriate temps.  This tests whether doit methods are debuggable
  	 since they carry their own temps."
  	self closureCases do:
  		[:source| | mn om m mbe obe |
  		mn := source first isLetter
  					ifTrue:
  						[self class newCompiler
  							compile: source
  							in: self class
  							notifying: nil
  							ifFail: [self error: 'compilation error']]
  					ifFalse:
  						[self class newCompiler
  							compileNoPattern: source
  							in: self class
- 							context: nil
  							notifying: nil
  							ifFail: [self error: 'compilation error']].
  		m := (om := mn generate) copyWithTempsFromMethodNode: mn.
  		self assert: m holdsTempNames.
  		self assert: m endPC = om endPC.
  		mbe := m blockExtentsToTempsMap.
  		obe := mn blockExtentsToTempsMap.
  		self assert: mbe keys asSet = obe keys asSet.
  		(mbe keys intersection: obe keys) do:
  			[:interval|
  			self assert: (mbe at: interval) = (obe at: interval)]]!

Item was changed:
  ----- Method: CompilerTest>>testBinarySelectorWithBar (in category 'syntax') -----
  testBinarySelectorWithBar
  	"Acknowledge the fact that $| is now allowed at any place in a binary selector"
  	
  	#(#'||' #'|||' #'|||++' #'<|>') do: [:selector | | source tree |
  		source := ('1 ' , selector , ' 2') readStream.
  		tree := (Compiler new)
+ 			compileNoPattern: source in: Object notifying: nil ifFail: [nil].
- 			compileNoPattern: source in: Object context: nil notifying: nil ifFail: [nil].
  		self assert: tree notNil.
  	
  		"Hem, this test is really ugly..."
  		self assert: tree block statements first expr selector key = selector].!

Item was changed:
  ----- Method: CompilerTest>>testBinarySelectorWithMinus (in category 'syntax') -----
  testBinarySelectorWithMinus
  	"Acknowledge the fact that $- is now allowed at any place in a binary selector"
  	
  	| source tree |
  	source := '1 @- 2' readStream.
  	tree := (Compiler new)
+ 			compileNoPattern: source in: Object notifying: nil ifFail: [nil].
- 			compileNoPattern: source in: Object context: nil notifying: nil ifFail: [nil].
  	self assert: tree notNil.
  	
  	"Hem, this test is really ugly..."
  	self assert: tree block statements first expr selector key = #'@-'.!

Item was changed:
  ----- Method: DecompilerTests>>testDecompileAnswerToDoLoop (in category 'tests') -----
  testDecompileAnswerToDoLoop
  	"This is a non regression test for Compiler-nice.224."
  	"DecompilerTests new testDecompileAnswerToDoLoop"
  	| sourceCode mn decompiledCode  |
  	sourceCode := '^nil to: 3 do: [:i| i class]'.
  	self
+ 		shouldnt: [mn := self class newCompiler compileNoPattern: sourceCode in: self class notifying: nil ifFail: [self error: 'failed']]
- 		shouldnt: [mn := self class newCompiler compileNoPattern: sourceCode in: self class context: nil notifying: nil ifFail: [self error: 'failed']]
  		raise: Error.
  	self
  		shouldnt: [decompiledCode := mn generateWithTempNames decompileWithTemps asString]
  		raise: Error.
  	"This to avoid getting fooled by changes in decompilation due to code formatting preferences."
  	decompiledCode := decompiledCode copyReplaceAll: {Character cr. Character tab. Character tab } with: ' '.
  	decompiledCode := decompiledCode copyReplaceAll: '^ ' with: '^'.
  	decompiledCode := decompiledCode copyReplaceAll: ' |' with: '|'.
  	self
  		assert: (decompiledCode endsWith: sourceCode)
  		description: 'decompilation should match source'.!

Item was changed:
  ----- Method: MCStWriterTest>>assertChunkIsWellFormed: (in category 'asserting') -----
  assertChunkIsWellFormed: chunk
  	self class newParser
  		parse: chunk readStream 
  		class: UndefinedObject 
  		noPattern: true
- 		context: nil
  		notifying: nil
  		ifFail: [self assert: false]!

Item was changed:
  ----- Method: MCStWriterTest>>assertMethodChunkIsWellFormed: (in category 'asserting') -----
  assertMethodChunkIsWellFormed: chunk
  	self class newParser
  		parse: chunk readStream 
  		class: UndefinedObject 
  		noPattern: false
- 		context: nil
  		notifying: nil
  		ifFail: [self assert: false]!



More information about the Packages mailing list