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

commits at source.squeak.org commits at source.squeak.org
Sat Jan 23 00:16:45 UTC 2016


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

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

Name: VMMaker.oscog-eem.1662
Author: eem
Time: 23 January 2016, 4:15:00.048507 pm
UUID: 686f2648-1716-445e-8440-ec23d22489a5
Ancestors: VMMaker.oscog-eem.1661

Slang: Fix bad regression in type inference from VMMaker.oscog-eem.1587.  returnTypeForSend:in: can only default return types to sqInt for unknown sdelectors.  The rewrite in VMMaker.oscog-eem.1587 inadvertently defaulted the return type of known methods whose return type was yet to be determined to sqInt.  The fix is to only default to sqInt if there is no known method for the given selector.  This fixes the weird flipping of the type of 32-bit Spur's headerWhileForwardingOf:

StackInterpreterSimulator: determine the endPC of a method without depending on Cogit.  This allows StackInterpreter to do symbolicMethod: also.

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

Item was changed:
  ----- Method: CCodeGenerator>>returnTypeForSend:in: (in category 'type inference') -----
  returnTypeForSend: sendNode in: aTMethod
  	"Answer the return type for a send.  Absent sends default to #sqInt.
  	 The bitwise operators answer unsigned versions of their argument types, at least in gcc
  	 although this author can't find that in the C99 spec.  If you can find this, please let me know."
+ 	| sel methodOrNil |
+ 	methodOrNil := self anyMethodNamed: (sel := sendNode selector).
+ 	(methodOrNil notNil and: [methodOrNil returnType notNil]) ifTrue:
+ 		[^self baseTypeForType: methodOrNil returnType].
- 	| sel |
- 	(self anyMethodNamed: (sel := sendNode selector)) ifNotNil:
- 		[:m|
- 		m returnType ifNotNil: [:type| ^self baseTypeForType: type]].
  	^kernelReturnTypes
  		at: sel
  		ifAbsent:
  			[sel
  				caseOf: {
  				[#+]					->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#-]						->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#*]					->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#/]						->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#addressOf:]			->	[(self typeFor: sendNode receiver in: aTMethod)
  												ifNil: [#sqInt]
  												ifNotNil: [:type| type, (type last isLetter ifTrue: [' *'] ifFalse: ['*'])]].
  				[#at:]					->	[self typeForDereference: sendNode in: aTMethod].
  				[#bitAnd:]				->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#bitOr:]				->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#bitXor:]				->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#asFloat]				->	[#double].
  				[#atan]					->	[#double].
  				[#exp]					->	[#double].
  				[#log]					->	[#double].
  				[#sin]					->	[#double].
  				[#sqrt]					->	[#double].
  				[#asLong]				->	[#long].
  				[#asUnsignedInteger]	->	[#usqInt].
  				[#asUnsignedLong]		->	[#'unsigned long'].
  				[#asVoidPointer]		->	[#'void *'].
  				[#signedIntToLong]		->	[#usqInt]. "c.f. generateSignedIntToLong:on:indent:"
  				[#signedIntToShort]	->	[#usqInt]. "c.f. generateSignedIntToShort:on:indent:"
  				[#cCoerce:to:]			->	[sendNode args last value].
  				[#cCoerceSimple:to:]	->	[sendNode args last value].
  				[#ifTrue:ifFalse:]		->	[self typeForConditional: sendNode in: aTMethod].
  				[#ifFalse:ifTrue:]		->	[self typeForConditional: sendNode in: aTMethod].
  				[#ifTrue:]				->	[self typeForConditional: sendNode in: aTMethod].
  				[#ifFalse:]				->	[self typeForConditional: sendNode in: aTMethod] }
+ 				otherwise: "If there /is/ a method for sel but its retrn type is as yet unknown we /mustn't/ default it.
+ 							We can only default unbound selectors."
+ 					[methodOrNil ifNotNil: [nil] ifNil: [#sqInt]]]!
- 				otherwise: [#sqInt]]!

Item was added:
+ ----- Method: StackInterpreterSimulator>>cogit (in category 'simulation only') -----
+ cogit
+ 	"We don't have a cogit; try and get by on our own devices."
+ 	^self!

Item was added:
+ ----- Method: StackInterpreterSimulator>>endPCOf: (in category 'compiled methods') -----
+ endPCOf: aMethod
+ 	"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]] }
+ 			otherwise: [].
+ 		 pc := is pc - 1].
+ 	^end!



More information about the Vm-dev mailing list