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

commits at source.squeak.org commits at source.squeak.org
Wed Jan 6 16:40:55 UTC 2016


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

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

Name: VMMaker.oscog-eem.1618
Author: eem
Time: 5 January 2016, 8:39:14.797875 am
UUID: 52b779fd-f223-4a12-8c51-5e10a3cf4a8b
Ancestors: VMMaker.oscog-cb.1617

Spur: Get initialization right so that #Spur32/64BitMemoryManager is defined to enable/disable the SmallFloat primitives in the interpreter too.

Fix a regression in genPrimitiveSmallFloatSquareRoot.

Revert some unchanged timestamps and correct an obsolete comment.

=============== Diff against VMMaker.oscog-cb.1617 ===============

Item was changed:
  ----- Method: CogVMSimulator>>maybeCheckStackDepth:sp:pc: (in category 'debug support') -----
  maybeCheckStackDepth: delta sp: sp pc: mcpc
  	| asp bcpc startbcpc cogHomeMethod cogBlockMethod csp debugStackPointers |
  	debugStackDepthDictionary ifNil: [^self].
  	(self isMachineCodeFrame: framePointer) ifFalse: [^self].
  	cogBlockMethod := self mframeCogMethod: framePointer.
  	cogHomeMethod := self asCogHomeMethod: cogBlockMethod.
  	debugStackPointers := debugStackDepthDictionary
  								at: cogHomeMethod methodObject
  								ifAbsentPut: [self debugStackPointersFor: cogHomeMethod methodObject].
  	startbcpc := cogHomeMethod = cogBlockMethod
  					ifTrue: [self startPCOfMethod: cogHomeMethod methodObject]
  					ifFalse: [self startPCOfClosure: (self pushedReceiverOrClosureOfFrame: framePointer)].
  	bcpc := cogit bytecodePCFor: mcpc startBcpc: startbcpc in: cogBlockMethod.
  	self assert: bcpc ~= 0.
  	cogBlockMethod ~= cogHomeMethod ifTrue:
  		[| lastbcpc |
  		 lastbcpc := cogit lastBytecodePCForBlockAt: startbcpc in: cogHomeMethod methodObject.
  		 bcpc > lastbcpc ifTrue:
  			[bcpc := lastbcpc]].
  	asp := self stackPointerIndexForFrame: framePointer WithSP: sp + objectMemory wordSize.
  	csp := debugStackPointers at: bcpc.
  	"Compensate lazily for absent receiver sends."
  	(NewspeakVM
  	 and: [asp - delta = csp
  	 and: [cogit isAbsentReceiverSendAt: mcpc in: cogHomeMethod]]) ifTrue:
  		[csp := debugStackPointers at: bcpc put: csp + 1].
  	self assert: asp - delta + 1 = csp!

Item was removed:
- ----- Method: Spur32BitCoMemoryManager class>>initializeWithOptions: (in category 'class initialization') -----
- initializeWithOptions: optionsDictionary
- 	"SpurMemoryManager initializeWithOptions: Dictionary new"
- 
- 	optionsDictionary at: #Spur32BitMemoryManager put: true.
- 	super initializeWithOptions: optionsDictionary!

Item was added:
+ ----- Method: Spur32BitMemoryManager class>>initializeWithOptions: (in category 'class initialization') -----
+ initializeWithOptions: optionsDictionary
+ 	"SpurMemoryManager initializeWithOptions: Dictionary new"
+ 
+ 	optionsDictionary at: #Spur32BitMemoryManager put: true.
+ 	super initializeWithOptions: optionsDictionary!

Item was removed:
- ----- Method: Spur64BitCoMemoryManager class>>initializeWithOptions: (in category 'class initialization') -----
- initializeWithOptions: optionsDictionary
- 	"SpurMemoryManager initializeWithOptions: Dictionary new"
- 
- 	optionsDictionary at: #Spur64BitMemoryManager put: true.
- 	super initializeWithOptions: optionsDictionary!

Item was added:
+ ----- Method: Spur64BitMemoryManager class>>initializeWithOptions: (in category 'class initialization') -----
+ initializeWithOptions: optionsDictionary
+ 	"SpurMemoryManager initializeWithOptions: Dictionary new"
+ 
+ 	optionsDictionary at: #Spur64BitMemoryManager put: true.
+ 	super initializeWithOptions: optionsDictionary!

Item was changed:
  ----- Method: SpurMemoryManager>>clone: (in category 'allocation') -----
  clone: objOop
  	| numSlots fmt newObj |
  	numSlots := self numSlotsOf: objOop.
  	fmt := self formatOf: objOop.
  	numSlots > self maxSlotsForNewSpaceAlloc
  		ifTrue:
  			[newObj := self allocateSlotsInOldSpace: numSlots
  							format: fmt
  							classIndex: (self classIndexOf: objOop)]
  		ifFalse:
  			[newObj := self allocateSlots: numSlots
  							format: fmt
  							classIndex: (self classIndexOf: objOop)].
  	newObj ifNil:
  		[^0].
  	(self isPointersFormat: fmt)
  		ifTrue:
  			[| hasYoung |
  			 hasYoung := false.
  			 0 to: numSlots - 1 do:
  				[:i| | oop |
  				oop := self fetchPointer: i ofObject: objOop.
  				(self isNonImmediate: oop) ifTrue:
  					[(self isForwarded: oop) ifTrue:
  						[oop := self followForwarded: oop].
  					((self isNonImmediate: oop)
  					 and: [self isYoungObject: oop]) ifTrue:
  						[hasYoung := true]].
  				self storePointerUnchecked: i
  					ofObject: newObj
  					withValue: oop].
  			(hasYoung
  			 and: [(self isYoungObject: newObj) not]) ifTrue:
  				[scavenger remember: newObj]]
  		ifFalse:
  			[0 to: numSlots - 1 do:
  				[:i|
  				self storePointerUnchecked: i
  					ofObject: newObj
  					withValue: (self fetchPointer: i ofObject: objOop)].
  			 fmt >= self firstCompiledMethodFormat ifTrue:
  				[coInterpreter maybeFixClonedCompiledMethod: newObj.
  				 ((self isOldObject: newObj)
  				  and: [(self isYoungObject: objOop) or: [self isRemembered: objOop]]) ifTrue:
  					[scavenger remember: newObj]]].
  	^newObj!

Item was changed:
  ----- Method: StackInterpreter>>storeAndPopReceiverVariableBytecode (in category 'stack bytecodes') -----
  storeAndPopReceiverVariableBytecode
- 	"Note: This code uses 
- 	storePointerUnchecked:ofObject:withValue: and does the 
- 	store check explicitely in order to help the translator 
- 	produce better code."
  	| rcvr top |
  	rcvr := self receiver.
  	top := self internalStackTop.
  	self internalPop: 1.
  	self
  		cCode: "Slang will inline currentBytecode to a constant so this will work in C"
  			[self fetchNextBytecode.
  			 objectMemory
  				storePointerImmutabilityCheck: (currentBytecode bitAnd: 7)
  				ofObject: rcvr
  				withValue: top]
  		inSmalltalk: "But in Smalltalk we must use the currentBytecode's value, not the next. 
+ 					We cant use the following code when generating C code as slang 
+ 					won't inline currentBytecode correctly due to the extra temp."
- 			We cant use the following code when generating C code as slang 
- 			won't inline currentBytecode correctly due to the extra temp."
  			[ | instVarIndex |
  			 instVarIndex := currentBytecode bitAnd: 7.
  			 self fetchNextBytecode.
  			 objectMemory
  				storePointerImmutabilityCheck: instVarIndex
  				ofObject: rcvr
  				withValue: top]!

Item was changed:
  ----- Method: StackInterpreter>>trinaryInlinePrimitive: (in category 'miscellaneous bytecodes') -----
  trinaryInlinePrimitive: primIndex
  	"SistaV1:	248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution."
  	<option: #SistaVM>
  	| result |
  	primIndex caseOf: {
  
  		"3000	unchecked Pointer Object>>at:put:.			The receiver is guaranteed to be a pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger"
  		[0]	->	[result := self internalStackTop.
  				 objectMemory
  					storePointer: (objectMemory integerValueOf: (self internalStackValue: 1)) - 1
  					ofObject: (self internalStackValue: 2)
  					withValue: result.
  				 self internalPop: 2; internalStackTopPut: result].
  		"3001	unchecked Byte Object>>at:put:.			The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The argument is a SmallInteger.  The primitive stores the least significant 8 bits."
  		[1]	->	[result := self internalStackTop.
  				 objectMemory
  					storeByte: (objectMemory integerValueOf: (self internalStackValue: 1)) - 1
  					ofObject: (self internalStackValue: 2)
  					withValue: (objectMemory integerValueOf: result).
  				 self internalPop: 2; internalStackTopPut: result].
  		"3002	unchecked Word Object>>at:put:.			The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The argument is a SmallInteger.  The primitive stores the least significant 16 bits."
  		[2]	->	[result := self internalStackTop.
  				 objectMemory
  					storeShort16: (objectMemory integerValueOf: (self internalStackValue: 1)) - 1
  					ofObject: (self internalStackValue: 2)
  					withValue: (objectMemory integerValueOf: result).
  				 self internalPop: 2; internalStackTopPut: result].
  		"3003	unchecked DoubleWord Object>>at:put:.	The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The argument is a SmallInteger.  The primitive stores the least significant 32 bits."
  		[3]	->	[result := self internalStackTop.
  				 objectMemory
  					storeLong32: (objectMemory integerValueOf: (self internalStackValue: 1)) - 1
  					ofObject: (self internalStackValue: 2)
  					withValue: (objectMemory integerValueOf: result).
  				 self internalPop: 2; internalStackTopPut: result].
  		"3004	unchecked QuadWord Object>>at:put:.		The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The argument is a SmallInteger.  The primitive stores the least significant 64 bits."
  		[4]	->	[result := self internalStackTop.
  				 objectMemory
  					storeLong64: (objectMemory integerValueOf: (self internalStackValue: 1)) - 1
  					ofObject: (self internalStackValue: 2)
  					withValue: (objectMemory integerValueOf: result).
  				 self internalPop: 2; internalStackTopPut: result] }
  	otherwise:
  		[localIP := localIP - 3.
  		 self respondToUnknownBytecode]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPrimitiveSmallFloatSquareRoot (in category 'primitive generators') -----
  genPrimitiveSmallFloatSquareRoot
  	<option: #Spur64BitMemoryManager>
  	| jumpFailAlloc |
  	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
+ 	objectRepresentation genGetSmallFloatValueOf: ReceiverResultReg scratch: SendNumArgsReg into: DPFPReg0.
- 	objectRepresentation genGetSmallFloatValueOf: ReceiverResultReg into: DPFPReg0.
  	self SqrtRd: DPFPReg0.
  	jumpFailAlloc := objectRepresentation
  						genAllocFloatValue: DPFPReg0
  						into: SendNumArgsReg
  						scratchReg: ClassReg
  						scratchReg: TempReg.
  	self MoveR: SendNumArgsReg R: ReceiverResultReg.
  	self RetN: 0.
  	jumpFailAlloc jmpTarget: self Label.
  	^self compileFallbackToInterpreterPrimitive: 0!



More information about the Vm-dev mailing list