[squeak-dev] The Trunk: Tests-eem.96.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Oct 10 00:50:26 UTC 2010


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

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

Name: Tests-eem.96
Author: eem
Time: 9 October 2010, 5:50:13.075 pm
UUID: 8800404e-9468-4032-bee6-fe8400f7334a
Ancestors: Tests-eem.95

Reduce DecompilerTest failures to three legitimate failures.
Do so by restricting tests to base classes in 4.1, by using deocmpileWithTempNames: to eliminate temp orderig issues, and by adding a few expected failures (but eliminating many more).

The expected failures are due to incorrect printing of Array literals containing literal characters that have a name (Character space), and of decmpiling whiles that modify their limit as to:do:.

=============== Diff against Tests-eem.95 ===============

Item was changed:
  ----- Method: DecompilerTestFailuresCollector>>assert:description:resumable: (in category 'accessing') -----
  assert: aBoolean description: aString resumable: resumableBoolean 
  	aBoolean ifFalse: 
  		[failures isNil ifTrue:
  			[failures := OrderedCollection new].
+ 		 failures addLast: (thisContext sender home tempAt: 1) methodReference]!
- 		 failures addLast: (thisContext sender tempAt: 1) methodReference]!

Item was added:
+ ----- Method: DecompilerTestFailuresCollector>>checkDecompileMethod: (in category 'utilities') -----
+ checkDecompileMethod: oldMethod
+ 	
+ 	[^super checkDecompileMethod: oldMethod]
+ 		on: SyntaxErrorNotification
+ 		do: [:ex|
+ 			self assert: false 
+ 				description: 'syntax error'
+ 				resumable: true].!

Item was added:
+ ----- Method: DecompilerTestFailuresCollector>>computeFailures (in category 'accessing') -----
+ computeFailures
+ 	(DecompilerTests organization listAtCategoryNamed: #tests) do:
+ 		[:s|
+ 		(s beginsWith: 'testDecompilerInClasses') ifTrue:
+ 			[self perform: s]].
+ 	^failures!

Item was added:
+ ----- Method: DecompilerTestFailuresCollector>>isFailure:sel: (in category 'accessing') -----
+ isFailure: cls sel: selector
+ 	^false!

Item was removed:
- ----- Method: DecompilerTests>>blockingClasses (in category 'utilities') -----
- blockingClasses
- 
- 
- 	^ #(CompiledMethod)!

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)
- 	oldMethodNode := cls decompilerClass new
  						decompile: selector
  						in: cls
  						method: oldMethod.
  	[oldMethodNode properties includesKey: #warning] whileTrue:
  		[oldMethodNode properties removeKey: #warning].
  	oldCodeString := oldMethodNode decompileString.
  	methodNode := [cls compilerClass new
  						compile: oldCodeString
  						in: cls
  						notifying: nil
  						ifFail: []]
  						on: SyntaxErrorNotification
  						do: [:ex|
  							ex errorMessage = 'Cannot store into' ifTrue:
  								[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)
- 		 newCodeString := (cls decompilerClass new
  							decompile: selector
  							in: cls
  							method: newMethod) 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
  			description: cls name asString, ' ', selector asString
  			resumable: true]!

Item was added:
+ ----- Method: DecompilerTests>>classNames (in category 'utilities') -----
+ classNames
+ 	| base41packageCategories classNames |
+ 	"(SystemOrganization categories collect: [:ea| (ea copyUpTo: $-) asString]) asSet asSortedCollection asArray"
+ 	base41packageCategories :=
+ 		#(	'311Deprecated'
+ 			'Balloon'
+ 			'Collections' 'CollectionsTests' 'Compiler' 'Compression'
+ 			'Etoys' 'Exceptions'
+ 			'Files'
+ 			'Graphics' 'GraphicsTests'
+ 			'Help' 'HelpSystem'
+ 			'Installer'
+ 			'Kernel' 'KernelTests'
+ 			'Monticello' 'MonticelloConfigurations' 'Morphic' 'MorphicExtras' 'MorphicTests' 'Multilingual' 'MultilingualTests'
+ 			'Nebraska' 'Network' 'NetworkTests'
+ 			'PackageInfo' 'PreferenceBrowser' 'Protocols'
+ 			'ReleaseBuilder'
+ 			'SMBase' 'SMLoader' 'ST80' 'SUnit' 'SUnitGUI' 'ScriptLoader' 'Services' 'ShoutCore' 'Simulation' 'Sound' 'System' 'SystemChangeNotification'
+ 			'Tests' 'ToolBuilder' 'Tools' 'ToolsTests' 'Traits' 'TraitsTests' 'TrueType'
+ 			'Universes'
+ 			'VersionNumber' 'VersionNumberTests'
+ 			'XML') asSet.
+ 	classNames := Set new.
+ 	SystemOrganization categories do:
+ 		[:cat|
+ 		(base41packageCategories includes: (cat copyUpTo: $-) asString) ifTrue:
+ 			[classNames addAll: (SystemOrganization listAtCategoryNamed: cat)]].
+ 	^classNames asSortedCollection!

Item was changed:
  ----- Method: DecompilerTests>>decompileClassesSelect: (in category 'utilities') -----
  decompileClassesSelect: aBlock
+ 
+ 	(self classNames select: aBlock) do:
- 	
- 	(Smalltalk classNames select: aBlock) do:
  		[:cn | | cls |
  		cls := Smalltalk globals at: cn.
+ 		cls selectorsAndMethodsDo:
- 		 cls selectorsAndMethodsDo:
  			[:selector :meth |
  			(self isFailure: cls sel: selector) ifFalse:
+ 				[self checkDecompileMethod: meth]]]!
- 				[" to help making progress
- 					(self
- 						isStoredProblems: cls theNonMetaClass
- 						sel: selector
- 						meta: cls isMeta)
- 					ifFalse: [ "
- 				self checkDecompileMethod: meth]]]!

Item was added:
+ ----- Method: DecompilerTests>>decompileStringForParseTree: (in category 'utilities') -----
+ decompileStringForParseTree: aMethodNode
+ 	"Renumber the temps in the tree in parse tree order to eliminate that as a source of extraneous difference."
+ 	| visited count counter |
+ 	visited := IdentitySet new.
+ 	count := 0.
+ 	counter := [:temp|
+ 				(visited includes: temp) ifFalse:
+ 					[temp name: 't', (count := count + 1) printString.
+ 					 visited add: temp]].
+ 	aMethodNode nodesDo:
+ 		[:node|
+ 		(node == aMethodNode or: [node isBlockNode and: [node optimized not]]) ifTrue:
+ 			[node arguments do: counter].
+ 		node isTemp ifTrue:
+ 			[counter value: node]].
+ 	
+ 	aMethodNode nodesDo:
+ 		[:node|
+ 		(node == aMethodNode or: [node isBlockNode and: [node optimized not]]) ifTrue:
+ 			[node temporaries do: counter.
+ 			 node temporaries: (node temporaries asSortedCollection: ParseNode tempSortBlock) asArray]].
+ 	^aMethodNode decompileString!

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 via
+ 		DecompilerTestFailuresCollector new computeFailures collect:
+ 			[:mr| { mr classSymbol. mr selector }]) asArray"
- 	"here is the list of failures: DNU resulting in trying to decompile the following methods"
  
+ 	^#(	(BrowserCommentTextMorph showPane)
+ 		(ClassDescription replaceSilently:to:)
+ 		(CodeHolder getSelectorAndSendQuery:to:with:)
- 	^ #((AdditionalMethodState at:ifAbsent:)
- 		(AdditionalMethodState at:ifAbsentPut:)
- 		(AdditionalMethodState at:put:)
- 		(AdditionalMethodState hasLiteralSuchThat:)
- 		(AdditionalMethodState hasLiteralThorough:)
- 		(AdditionalMethodState includesProperty:)
- 		(AdditionalMethodState keysAndValuesDo:)
- 		(AdditionalMethodState pragmas)
- 		(AdditionalMethodState properties)
- 		(AdditionalMethodState propertyKeysAndValuesDo:)
- 		(AdditionalMethodState propertyValueAt:ifAbsent:)
- 		(AdditionalMethodState removeKey:ifAbsent:)
- 		(AdditionalMethodState setMethod:)
- 		(BalloonEngineSimulation circleCosTable "-0.3826834323650903 => -0.38268343236509 or -0.3826834323650902")
- 		 (BalloonEngineSimulation circleSinTable "-0.3826834323650903 => -0.38268343236509 or -0.3826834323650902")
- 		(BlockNode emitCodeExceptLast:encoder:)
- 		(BlockNode sizeCodeExceptLast:)
- 		(Categorizer changeFromCategorySpecs:)
- 		(Categorizer elementCategoryDict)
- 		(ChatNotes storeAIFFOnFile:)
- 		(ClosureTests testToDoInsideTemp)
- 		(Command veryDeepFixupWith:)
- 		(CompiledMethod =)
- 		(CompiledMethod allEmbeddedBlockMethods)
- 		(CompiledMethod embeddedBlockMethods)
- 		(CompiledMethod getPreambleFrom:at:)
- 		(CompiledMethod hasLiteralSuchThat:)
- 		(CompiledMethod hasLiteralThorough:)
- 		(CompiledMethod sameTraitCodeAs:)
  		(Date printOn:)
+ 		(FileDirectory checkForReadability)
- 		(DependencyBrowser computePackageDependencies:)
- 		(EventSensor eventTickler)
  		(Float printPaddedWith:to:)
+ 		(GIFReadWriter nextImageWithPlugin)
- 		(FMSound mixSampleCount:into:startingAt:leftVol:rightVol:)
- 		(Form preMultiplyAlpha)
- 		(FTPClient getDataInto:)
- 		 (GeniePlugin primSameClassAbsoluteStrokeDistanceMyPoints:otherPoints:myVectors:otherVectors:mySquaredLengths:otherSquaredLengths:myAngles:otherAngles:maxSizeAndReferenceFlag:rowBase:rowInsertRemove:rowInsertRemoveCount: "Cannot compile -- stack including temps is too deep")
- 		(GZipReadStream on:from:to:)
- 		(GraphMorph drawDataOn:)
  		(HttpUrl checkAuthorization:retry:)
+ 		(MCConfigurationBrowser post)
+ 		(MailComposition breakLinesInMessage:)
+ 		(MVCToolBuilder setLayout:in:) "same-name block-local temps in optimized blocks"
+ 		(ParagraphEditor inOutdent:delta:)
- 		(Integer asBytesDescription)
- 		(IntegerTest testNumberOfDigits)
- 		(IntegerTest testPrintStringBase)
- 		(JPEGReadWriter decodeBlockInto:component:dcTable:acTable:)
- 		(LoopedSampledSound mixSampleCount:into:startingAt:leftVol:rightVol:)
- 		(MessageTally treePrintOn:tabs:thisTab:total:totalTime:tallyExact:orThreshold:)
- 		(MessageTrace selectAllBetweenAnchorAnd:)
- 		(MethodPragmaTest testCompileCharacter)
- 		(MultiByteBinaryOrTextStream next:)
- 		(MultiByteFileStream next:)
- 		(MVCProject textWindows)
- 		(MVCToolBuilder setLayout:in:)
- 		(NewParagraph selectionRectsFrom:to:)
- 		(PackageDependencyTest testPackage:dependsExactlyOn:)
- 		(PasteUpMorph dropFiles:)
- 		(Player veryDeepFixupWith:)
- 		(PluggableTabButtonMorph calculateArcLengths)
- 		(PluggableTabButtonMorph drawTabOn:)
- 		(PluckedSound reset)
  		(PNGReadWriter copyPixelsGray:)
+ 		(PointTest testNormal) "fraction printing??"
+ 		(PointTest testTheta) "fraction printing??"
+ 		(ScaledDecimalTest testConvertFromFraction) "local/non-local temps"
+ 		(StandardScriptingSystem holderWithAlphabet) "same-name block-local temps in optimized blocks"
+ 		(SystemWindow convertAlignment)
+ 		(TextEditor inOutdent:delta:)
- 		(PNGReadWriter processInterlaced)
- 		(PNMReadWriter nextPutRGB:)
- 		(PNMReadWriter nextPutBW:reverse:)
- 		(PNMReadWriter readBWreverse:)
- 		(PNMReadWriter readGray)
- 		(PNMReadWriter readPlainRGB)
- 		(PNMReadWriter writeHeader:)
- 		(PointTest testTheta)
- 		(PopUpMenu readKeyboard)
- 		(PostscriptCanvas outlineQuadraticBezierShape:)
- 		(QPickable2D pick:) "foo ifTrue: [^bar] ifFalse: [^baz]. ^huh?"
- 		(QUsersPane userEntryCompare:to:) "foo ifTrue: [^bar] ifFalse: [^baz]. ^huh?"
- 		(RelativeInstructionPrinter print:)
- 		(RemoteHandMorph appendNewDataToReceiveBuffer)
- 		(ScaledDecimalTest testConvertFromFraction)
- 		(SHMCClassDefinition allInstVarNames)
- 		(SHMCClassDefinition withAllSuperclasses)
- 		(ShortIntegerArray writeOn:)
- 		(SHParserST80 isBinary)
- 		(StandardScriptingSystem holderWithAlphabet)
- 		(StrikeFontSet displayStringR2L:on:from:to:at:kern:)
- 		(String howManyMatch:)
- 		(String keywords)
- 		(StringTest testWthNoLineLongerThan)
- 		(SyntaxMorph replaceKeyWord:menuItem:)
- 		(SyntaxMorph replaceSel:menuItem:)
- 		(TextDiffBuilder lcsFor:and:)
  		(TextURL actOnClickFor:)
+ 		(TTContourConstruction segmentsDo:) "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:))!
- 		(TShaderProgram vertexStrings) "foo ifTrue: []. => foo. => ."
- 		(TShaderProgram fragmentStrings) "foo ifTrue: []. => foo. => ."
- 		(TTContourConstruction segmentsDo:) "out of scope variable"
- 		(TTCFontReader processCharacterMappingTable:)
- 		(TTFileDescription getGlyphFlagsFrom:size:)
- 		(TTFileDescription processCharacterMappingTable:)
- 		(TTFontReader getGlyphFlagsFrom:size:)
- 		(TTFontReader processCharacterMappingTable:)
- 		(TTFontReader processHorizontalMetricsTable:length:)
- 		(TWindow zoomWindow:) "foo ifTrue: [^bar] ifFalse: [^baz]. ^huh?"
- 		(WaveEditor showEnvelope)
- 		(WeakSet scanForLoadedSymbol:)
- 
- 		"(PNMReadWriter nextImage) (Collection #ifEmpty:ifNotEmpty:) (Collection #ifEmpty:) (Collection #ifNotEmpty:ifEmpty:) (Text #alignmentAt:ifAbsent:) (ObjectWithDocumentation propertyAt:ifAbsent:)")!

Item was changed:
  ----- Method: MCMethodDefinitionTest>>override (in category 'mocks') -----
  override ^ 1!




More information about the Squeak-dev mailing list