[Vm-dev] VM Maker: VMMaker.oscog-eem.2181.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Mar 24 18:46:41 UTC 2017


Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2181.mcz

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

Name: VMMaker.oscog-eem.2181
Author: eem
Time: 24 March 2017, 11:45:48.896507 am
UUID: 7d1ebe24-d033-4fd1-8c67-52106d2c2a42
Ancestors: VMMaker.oscog-eem.2180

Make attemptToComputeTempNamesFor: robust enough to cope with AssemblerAbsentClassImports.
Add the branchIf[Not]InstanceOf: bytecodes to the simulator's endPC calculation.

=============== Diff against VMMaker.oscog-eem.2180 ===============

Item was changed:
  ----- Method: Cogit class>>attemptToComputeTempNamesFor: (in category 'in-image compilation support') -----
  attemptToComputeTempNamesFor: aCompiledMethod
  	(aCompiledMethod respondsTo: #tempNames) ifTrue:
  		[| blocks |
  		 blocks := aCompiledMethod embeddedBlockClosures.
  		 initializationOptions
  			at: #tempNames
  			put: (Dictionary withAll: {aCompiledMethod initialPC -> ([aCompiledMethod tempNames]
  																		on: MessageNotUnderstood
  																		do: [:ex|
  																			(self isSistaMessage: ex message unimplementedIn: Decompiler) ifTrue:
  																				[^self].
+ 																			 (Smalltalk classNamed: #AssemblerAbsentClassImport) ifNotNil:
+ 																				[:aaciClass|
+ 																				 (ex receiver isKindOf: aaciClass) ifTrue:
+ 																					[^self]].
  																			 ex pass])},
  				(blocks
  					ifEmpty: [#()]
  					ifNotEmpty:
  						[aCompiledMethod embeddedBlockClosures
  							with: ((aCompiledMethod methodNode schematicTempNamesString allButFirst:
  									(aCompiledMethod methodNode schematicTempNamesString indexOf: $[)) piecesCutWhere: [:a :b| b = $[])
  							collect: [:c :s| c startpc -> s substrings]]))]!

Item was changed:
  ----- Method: StackInterpreterSimulator>>endPCOf: (in category 'compiled methods') -----
  endPCOf: aMethod
+ 	"Determine the endPC of a method in the heap using interpretation that looks for returns and uses branches to skip intervening bytecodes."
- 	"Determine the endPC of a method in the heap using interpretation that looks for returns."
- 	
- 	<var: #descriptor type: #'BytecodeDescriptor *'>
  	| pc end farthestContinuation prim encoderClass inst is |
  	(prim := self primitiveIndexOf: aMethod) > 0 ifTrue:
  		[(self isQuickPrimitiveIndex: prim) ifTrue:
  			[^(self startPCOfMethod: aMethod) - 1]].
  	encoderClass := self encoderClassForHeader: (objectMemory methodHeaderOf: aMethod).
  	is := (InstructionStream
  			on: (VMCompiledMethodProxy new
  					for: aMethod
  					coInterpreter: self
  					objectMemory: objectMemory)).
  	pc := farthestContinuation := self startPCOfMethod: aMethod.
  	end := objectMemory numBytesOf: aMethod.
  	is pc: pc + 1.
  	[pc <= end] whileTrue:
  		[inst := encoderClass interpretNextInstructionFor: MessageCatcher new in: is.
  		 inst selector
  			caseOf: {
  				 [#pushClosureCopyNumCopiedValues:numArgs:blockSize:]	
  											->	[is pc: is pc + inst arguments last.
  												 farthestContinuation := farthestContinuation max: pc].
  				 [#jump:]					->	[farthestContinuation := farthestContinuation max: pc + inst arguments first].
  				 [#jump:if:]					->	[farthestContinuation := farthestContinuation max: pc + inst arguments first].
  				 [#methodReturnConstant:]	->	[pc >= farthestContinuation ifTrue: [end := pc]].
  				 [#methodReturnReceiver]	->	[pc >= farthestContinuation ifTrue: [end := pc]].
  				 [#methodReturnTop]		->	[pc >= farthestContinuation ifTrue: [end := pc]].
  				"This is for CompiledBlock/FullBlockClosure.  Since the response to pushClosure... above
  				 skips over all block bytecoes, we will only see a blockReturnTop if it is at the top level,
  				 and so it must be a blockReturnTop in a CompiledBlock for a FullBlockClosure."
+ 				 [#blockReturnTop]			->	[pc >= farthestContinuation ifTrue: [end := pc]].
+ 				 [#branchIfInstanceOf:distance:]
+ 											->	[farthestContinuation := farthestContinuation max: pc + inst arguments last].
+ 				 [#branchIfNotInstanceOf:distance:]
+ 											->	[farthestContinuation := farthestContinuation max: pc + inst arguments last] }
- 				 [#blockReturnTop]			->	[pc >= farthestContinuation ifTrue: [end := pc]] }
  			otherwise: [].
  		 pc := is pc - 1].
  	^end!



More information about the Vm-dev mailing list