[Pkg] The Trunk: Tests-eem.409.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Mar 19 18:38:11 UTC 2019


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

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

Name: Tests-eem.409
Author: eem
Time: 19 March 2019, 11:38:09.260844 am
UUID: 7ba5d6e0-5b70-462f-a1ee-c77ab5b74dc3
Ancestors: Tests-eem.408

DecompilerTests:
Restrict the set of methods that are tested to thise in the base packages, excluding extensions from outside packages (this to eliminate errors due to _ assignment, etc).
Beef up checkDecompileMethod: to deal with both OutOfScopeNotification and SyntaxErrorNotification when the decompiler wrongly converts a while loop into a to:do: when the index is used out of scope.  Somehow the bytecode set affects which of these errors may be seen.
Eliminate some cases that used to fail and no longer do (principally in ProtoObjectTest testIfNotNil et al).
With these changes I see DecompilerTests all green in both 32-bit trunk and a trunk-derived 64-bit VMMaker image using SistaV1.

=============== Diff against Tests-eem.408 ===============

Item was added:
+ ----- Method: DecompilerTests>>basePackagePrefixes (in category 'utilities') -----
+ basePackagePrefixes
+ 	^#("'Balloon'" "AbstractAnimation>>prologue: in Balloon3D-Wonderland-Time breaks the test"
+ 		'Chronology' 'Collections' 'CommandLine' 'Compiler' 'Compression'
+ 		'Environments' 'Exceptions'
+ 		'Files'
+ 		'GetText' 'Graphics' 'Help-' 'HelpSystem-'
+ 		'Installer-Core'
+ 		'Kernel-' 'KernelTests-'
+ 		'Monticello'
+ 		'Morphic-' 'MorphicExtras-' 'MorphicExtrasTests-' 'MorphicTests-'
+ 		'Multilingual' 'MultilingualTests'
+ 		'Nebraska' 'Network' 'NetworkTests'
+ 		'PackageInfo-Base' 'PreferenceBrowser' 'Protocols'
+ 		'Regex'
+ 		'ReleaseBuilder'
+ 		'SMBase' 'SMLoader' 'ST80' 'ST80Tests' 'ST80Tools' 'SUnit' 'ScriptLoader' 'Services-Base' 'Shout' 
+ 			'Sound' 'Squeak-Version' 'SqueakSSL' 'System' 
+ 		'Tests' 'ToolBuilder' 'Tools' 'Traits' 'TrueType'
+ 		'Universes' 'UpdateStream' 'VersionNumber'
+ 		'WebClient-'
+ 		'XML-')!

Item was changed:
  ----- Method: DecompilerTests>>checkDecompileMethod: (in category 'utilities') -----
  checkDecompileMethod: oldMethod
  	
  	| cls selector oldMethodNode methodNode newMethod oldCodeString newCodeString |
  	cls := oldMethod methodClass.
  	selector := oldMethod selector.
  	oldMethodNode := (cls decompilerClass new withTempNames: oldMethod methodNode schematicTempNamesString)
  							decompile: selector
  							in: cls
  							method: oldMethod methodForDecompile.
  	[oldMethodNode properties includesKey: #warning] whileTrue:
  		[oldMethodNode properties removeKey: #warning].
  	oldCodeString := oldMethodNode decompileString.
+ 	methodNode := [[| compiler |
+ 					   compiler := cls newCompiler.
+ 					   compiler parser encoderClass: oldMethod encoderClass.
+ 					   compiler
- 	methodNode := [| compiler |
- 					  compiler := cls newCompiler.
- 					  compiler parser encoderClass: oldMethod encoderClass.
- 					  compiler
  						compile: oldCodeString
  						in: cls
  						notifying: nil
  						ifFail: []]
  						on: SyntaxErrorNotification
  						do: [:ex|
  							ex errorMessage = 'Cannot store into' ifTrue:
  								[ex return: #badStore].
+ 							ex pass]]
+ 						on: OutOfScopeNotification
+ 						do: [:ex| ex return: #badStore].
- 							ex pass].
  	"Ignore cannot store into block arg errors; they're not our issue."
  	methodNode ~~ #badStore ifTrue:
  		[newMethod := methodNode generate.
  		 newCodeString := ((cls decompilerClass new withTempNames: methodNode schematicTempNamesString)
  								decompile: selector
  								in: cls
  								method: newMethod methodForDecompile) decompileString.
  		 "(StringHolder new textContents:
  			(TextDiffBuilder buildDisplayPatchFrom: oldCodeString to: newCodeString))
  				openLabel: 'Decompilation Differences for ', cls name,'>>',selector"
  		 "(StringHolder new textContents:
  			(TextDiffBuilder buildDisplayPatchFrom: oldMethod abstractSymbolic to: newMethod abstractSymbolic))
  				openLabel: 'Bytecode Differences for ', cls name,'>>',selector"
  		 self assert: (oldCodeString = newCodeString
  					or: [(Scanner new scanTokens: oldCodeString) = (Scanner new scanTokens: newCodeString)])
  			description: cls name asString, ' ', selector asString
  			resumable: true]!

Item was changed:
  ----- Method: DecompilerTests>>classNames (in category 'utilities') -----
  classNames
  	"A list of the classes in most of the base packages; excluding EToys arbitrarily for now"
  	^Smalltalk globals allClassesAndTraits
  		select:
  			[:classOrTrait|
+ 			 self basePackagePrefixes anySatisfy:
- 			 #(	'Balloon'
- 				'Chronology' 'Collections' 'CommandLine' 'Compiler' 'Compression'
- 				'Environments' 'Exceptions'
- 				'Files'
- 				'GetText' 'Graphics' 'Help-' 'HelpSystem-'
- 				'Installer-Core'
- 				'Kernel-' 'KernelTests-'
- 				'Monticello'
- 				'Morphic-' 'MorphicExtras-' 'MorphicExtrasTests-' 'MorphicTests-'
- 				'Multilingual' 'MultilingualTests'
- 				'Nebraska' 'Network' 'NetworkTests'
- 				'PackageInfo-Base' 'PreferenceBrowser' 'Protocols'
- 				'Regex'
- 				'ReleaseBuilder'
- 				'SMBase' 'SMLoader' 'ST80' 'ST80Tests' 'ST80Tools' 'SUnit' 'ScriptLoader' 'Services-Base' 'Shout' 
- 					'Sound' 'Squeak-Version' 'SqueakSSL' 'System' 
- 				'Tests' 'ToolBuilder' 'Tools' 'Traits' 'TrueType'
- 				'Universes' 'UpdateStream' 'VersionNumber'
- 				'WebClient-'
- 				'XML-') anySatisfy:
  				[:packageRoot|
  				 classOrTrait category ifNil: [false] ifNotNil: [:cat| cat beginsWith: packageRoot]]]
  		thenCollect:
  			[:classOrTrait| classOrTrait name]!

Item was changed:
  ----- Method: DecompilerTests>>decompileClassesSelect: (in category 'utilities') -----
  decompileClassesSelect: aBlock
  
+ 	CurrentReadOnlySourceFiles cacheDuring:
+ 		[ (self classNames select: aBlock) do:
+ 			[ :cn | | class |
+ 			(class := Smalltalk classNamed: cn) selectorsAndMethodsDo:
+ 				[ :selector :method |
+ 				(self isUnacceptableExtension: selector inClass: class) ifFalse:
+ 					[(self exceptionClassForFailureFor: class selector: selector)
+ 						ifNil: [ self checkDecompileMethod: method ]
+ 						ifNotNil:
+ 							[ :exceptionClass |
+ 							self
+ 								should: [ self checkDecompileMethod: method ]
+ 								raise: exceptionClass ] ] ] ] ]!
- 	CurrentReadOnlySourceFiles cacheDuring: [
- 		(self classNames select: aBlock) do: [ :cn |
- 			| class |
- 			(class := Smalltalk classNamed: cn) selectorsAndMethodsDo: [ :selector :method |
- 			(self exceptionClassForFailureFor: class  selector: selector)
- 				ifNil: [ self checkDecompileMethod: method ]
- 				ifNotNil: [ :exceptionClass |
- 					self
- 						should: [ self checkDecompileMethod: method ]
- 						raise: exceptionClass ] ] ] ]!

Item was changed:
  ----- Method: DecompilerTests>>decompilerFailures (in category 'utilities') -----
  decompilerFailures
  	"Here is the list of failures: either a syntax error, a hard error or some failure to decompile correctly.
+ 	 Collected initially via 
+ 		DecompilerTestFailuresCollector new computeFailures.
+ 	 But can be maintained manually."
- 	 Collected via 
- 		DecompilerTestFailuresCollector new computeFailures."
  
  	"class name, selector, error class name or nil"
+ 	^#(
- 	^  #(
  		#(BrowserCommentTextMorph showPane SyntaxErrorNotification) 
  		#(CodeHolder getSelectorAndSendQuery:to:with: SyntaxErrorNotification) 
  		#(DecompilerTests testDecompileUnreachableParameter Error) 
  		#(MVCToolBuilder setLayout:in: SyntaxErrorNotification) "same-name block-local temps in optimized blocks"
+ 		#(Pen web AssertionFailure) "needs a recompile to compute remote temps correctly (repeat now inlined)"
+ 		#(PNGReadWriter copyPixelsGray: SyntaxErrorNotification)
+ 		#(Random roll: AssertionFailure) "needs a recompile to compute remote temps correctly (repeat now inlined)"
+ 		#(SHMCClassDefinition withAllSuperclassesDo: SyntaxErrorNotification)), "same-name block-local temps in optimized blocks"
+ 	 (Scanner allowBlockArgumentAssignment
+ 		ifTrue: [#()]
+ 		ifFalse:
+ 			[#(
+ 		#(NebraskaSenderMorph hideField: SyntaxErrorNotification)) "assigns into block argument"])!
- 		#(PNGReadWriter copyPixelsGray: SyntaxErrorNotification) 
- 		#(ProtoObjectTest testIfNilIfNotNil SyntaxErrorNotification) 
- 		#(ProtoObjectTest testIfNotNil SyntaxErrorNotification) 
- 		#(ProtoObjectTest testIfNotNilIfNil SyntaxErrorNotification)
- 		#(SHMCClassDefinition withAllSuperclassesDo: SyntaxErrorNotification) "same-name block-local temps in optimized blocks"
- 		#(TTContourConstruction segmentsDo: SyntaxErrorNotification) "Worth fixing; these two are mistaken conversion from a whileTrue: to a to:do: but the index is used outside the whileTrue:"
- 		#(TTFontReader processHorizontalMetricsTable:length: SyntaxErrorNotification))
- 
- !

Item was added:
+ ----- Method: DecompilerTests>>isUnacceptableExtension:inClass: (in category 'utilities') -----
+ isUnacceptableExtension: selector inClass: class
+ 	"Filter-out extensions outside the base packages"
+ 	| category |
+ 	category := class whichCategoryIncludesSelector: selector.
+ 	^category notEmpty
+ 	 and: [category first == $*
+ 	 and: [category := category allButFirst.
+ 		self basePackagePrefixes noneSatisfy: [:prefix| category beginsWith: prefix]]]!



More information about the Packages mailing list