[squeak-dev] The Inbox: Tests-fm.302.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Aug 14 02:42:58 UTC 2014


A new version of Tests was added to project The Inbox:
http://source.squeak.org/inbox/Tests-fm.302.mcz

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

Name: Tests-fm.302
Author: fm
Time: 13 August 2014, 10:42:44.901 pm
UUID: ce0f51fa-97a9-4c48-be91-c281f9a63c7b
Ancestors: Tests-fbs.301

make the decompiler tests also check class-side methods, they were skipped

do some more thorough checking for methods: 
  make sure the decompiled code is compileable
  also check decompiling without temp names, even if temp names are available, since the code paths are slightly different
  try to be more forgiving than exact string comparison for sources by checking first if the compiled methods are equal, then, if that fails, if the compiled methods' abstractSymbolic strings are equal and only if that also fails do the full source comparison

=============== Diff against Tests-fbs.301 ===============

Item was changed:
  ----- Method: DecompilerTests>>checkDecompileMethod: (in category 'utilities') -----
+ checkDecompileMethod: meth
- checkDecompileMethod: oldMethod
  	
+ 	| cls selector tempNames source methNode recompiled dMethNode dReparsed dRecompiled ungeneratedMethNode comparable
+ 	successWithTempNames |
+ 	cls := meth methodClass.
+ 	selector := meth selector.
+ 	source := meth getSourceNoDecompile.
+ 	source notNil ifTrue:
+ 		[methNode := [cls newCompiler
+ 									parse: source
+ 									in: cls
+ 									notifying: nil]
+ 								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."
+ 		methNode == #badStore ifTrue:
+ 			[^self].
+ 		methNode nodesDo: [:n | n comment: nil].
+ 		recompiled := [methNode generate: CompiledMethodTrailer defaultMethodTrailer]
+ 									on: UndeclaredVariableWarning
+ 									do: [:ex|
+ 										ex return: #undeclared].
+ 		ungeneratedMethNode := cls newCompiler
+ 										parse: source
+ 										in: cls
+ 										notifying: nil.
+ 		ungeneratedMethNode nodesDo: [:n | n comment: nil]].
+ 	meth holdsTempNames
+ 		ifTrue: [tempNames := meth tempNamesString]
+ 		ifFalse:
+ 			[source notNil ifTrue:
+ 				["Do not ignore (or auto-declare as globals) undeclared variables"
+ 				recompiled ~~ #undeclared ifTrue:
+ 					[tempNames := methNode schematicTempNamesString]]].
+ 
+ 	tempNames notNil ifTrue: 
+ 		[dMethNode := [(meth decompilerClass new withTempNames: tempNames)
+ 									decompile: selector
+ 									in: cls
+ 									method: meth]
+ 								on: UndeclaredVariableWarning
+ 								do: [:ex|
+ 									ex return: #outOfBoundsInstvar].
+ 		dMethNode ~~ #outOfBoundsInstvar ifTrue:
+ 			[[dMethNode properties includesKey: #warning] whileTrue:
+ 				[dMethNode properties removeKey: #warning].
+ 			dReparsed := [cls newCompiler
+ 									parse: dMethNode decompileString
+ 									in: cls
+ 									notifying: nil]
+ 								on: SyntaxErrorNotification
+ 								do: [:ex|
+ 									ex return: #unparseableDecompiled].
+ 			dReparsed ~~ #unparseableDecompiled ifTrue:
+ 				[dRecompiled := [dReparsed generate: CompiledMethodTrailer defaultMethodTrailer]
+ 										on: UndeclaredVariableWarning
+ 										do: [:ex|
+ 											ex return: #undeclared]]].
+ 		successWithTempNames := dRecompiled ~~ #undeclared and: 
+ 					[dMethNode ~~ #outOfBoundsInstvar and: 
+ 					[dReparsed ~~ #unparseableDecompiled and:
+ 					[meth = dRecompiled or: 
+ 						[meth abstractSymbolic = dRecompiled abstractSymbolic or: 
+ 						[(recompiled notNil and: [recompiled ~~ #undeclared and: [
+ 							recompiled = dRecompiled or: 
+ 							[recompiled abstractSymbolic = dRecompiled abstractSymbolic]]]) or:
+ 						[(methNode notNil and: [methNode decompileString = dMethNode decompileString]) or:
+ 						[ungeneratedMethNode notNil and: [ungeneratedMethNode decompileString = dMethNode decompileString]]]]]]]].
+ 		self assert: successWithTempNames
+ 				description: cls name asString, ' ', selector asString
+ 				resumable: true.
+ 		(tempNames = '' or: [successWithTempNames not]) ifTrue: 
+ 			"we already did the check ''without'' tempNames, or we already failed"
+ 			[^self]
+ 		].
+ 
+ 	"Do a check without tempNames even if we did check with tempNames, since it tests different codepaths"
+ 	dMethNode := [meth decompilerClass new
+ 									decompile: selector
+ 									in: cls
+ 									method: meth]
+ 						on: UndeclaredVariableWarning
- 	| 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 := [cls newCompiler
- 						compile: oldCodeString
- 						in: cls
- 						notifying: nil
- 						ifFail: []]
- 						on: SyntaxErrorNotification
  						do: [:ex|
+ 							ex return: #outOfBoundsInstvar].
+ 	dMethNode ~~ #outOfBoundsInstvar ifTrue:
+ 			[[dMethNode properties includesKey: #warning] whileTrue:
+ 					[dMethNode properties removeKey: #warning].
+ 			dReparsed := [cls newCompiler
+ 									parse: dMethNode decompileString
+ 									in: cls
+ 									notifying: nil]
+ 								on: SyntaxErrorNotification
+ 								do: [:ex|
+ 									ex return: #unparseableDecompiled].
+ 			dReparsed ~~ #unparseableDecompiled ifTrue:
+ 				[dRecompiled := [dReparsed generate]
+ 									on: UndeclaredVariableWarning
+ 									do: [:ex|
+ 										ex return: #undeclared]].
+ 			source notNil ifTrue:
+ 				[recompiled := [(cls newCompiler
+ 										parse: source
+ 										in: cls
+ 										notifying: nil) 
+ 									generate]
+ 								on: UndeclaredVariableWarning
+ 								do: [:ex|
+ 									ex return: #undeclared]]].
+ 	comparable := meth copyWithTrailerBytes: CompiledMethodTrailer empty.
+ 	self assert: (dRecompiled ~~ #undeclared and: [dMethNode ~~ #outOfBoundsInstvar and: [dReparsed ~~ #unparseableDecompiled and:
+ 					[comparable = dRecompiled or: 
+ 					[comparable abstractSymbolic = dRecompiled abstractSymbolic or:
+ 					[(recompiled notNil and: [recompiled ~~ #undeclared and: [
+ 						recompiled = dRecompiled or: 
+ 						[recompiled abstractSymbolic = dRecompiled abstractSymbolic]]]) or:
+ 					"there is no point in doing the source comparison checks if the method has args or temps"
+ 					[tempNames isNil and: [source notNil and:
+ 						[methNode schematicTempNamesString ~= '' or:
+ 						[methNode decompileString = dMethNode decompileString or:
+ 						[ungeneratedMethNode decompileString = dMethNode decompileString]]]]]]]]]])
- 							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)
- 								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
  			description: cls name asString, ' ', selector asString
+ 			resumable: true!
- 			resumable: true]!

Item was changed:
  ----- Method: DecompilerTests>>decompileClassesSelect: (in category 'utilities') -----
  decompileClassesSelect: aBlock
  
  	CurrentReadOnlySourceFiles cacheDuring: [
  		(self classNames select: aBlock) do:
  			[:cn | | cls |
  			cls := Smalltalk globals at: cn.
  			cls selectorsAndMethodsDo:
  				[:selector :meth |
  				(self isFailure: cls sel: selector) ifFalse:
+ 					[self checkDecompileMethod: meth methodForDecompile]].
+ 			cls := cls theMetaClass.
+ 			cls selectorsAndMethodsDo:
+ 				[:selector :meth |
+ 				(self isFailure: cls sel: selector) ifFalse:
+ 					[self checkDecompileMethod: meth methodForDecompile]]]]
+  !
- 					[self checkDecompileMethod: meth]]]]!



More information about the Squeak-dev mailing list