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

commits at source.squeak.org commits at source.squeak.org
Thu Aug 7 14:17:27 UTC 2014


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

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

Name: VMMaker.oscog-eem.846
Author: eem
Time: 7 August 2014, 7:14:40.362 am
UUID: 9e73d37e-0e43-4238-b471-c1c27d605caf
Ancestors: VMMaker.oscog-eem.845

Sista:
Implement ceClassTrap.

Fix argument access in inlinePrimitiveBytecode:.  Refactor
primitiveQuo to share code with inlinePrimitiveBytecode:.

Fix argument type of branches and its alloca
in genExtTrapIfNotInstanceOfBehaviorsBytecode.

Provide a dummy genCallPrimitiveBytecode for now.

Fix comment typos and miscategorizations.

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

Item was added:
+ ----- Method: CoInterpreter>>ceClassTrap: (in category 'trampolines') -----
+ ceClassTrap: anObject
+ 	<api>
+ 	<option: #SistaVM>
+ 	| context |
+ 	instructionPointer := self popStack.
+ 	context := self ensureFrameIsMarried: framePointer SP: stackPointer.
+ 	"If there is a class trap, the object is supposed to remain on
+ 	 the stack, but the cogit always removes it.  So restore it here."
+ 	self push: anObject.
+ 	self push: context.
+ 	self push: anObject.
+ 	self push: instructionPointer.
+ 	^self
+ 		ceSendAbort: (objectMemory splObj: SelectorClassTrap)
+ 		to: anObject
+ 		numArgs: 1!

Item was changed:
+ ----- Method: CoInterpreter>>frameNumTemps: (in category 'frame access') -----
- ----- Method: CoInterpreter>>frameNumTemps: (in category 'trampolines') -----
  frameNumTemps: theFP
  	"For subclasses to redefine to implement different closure semantics."
  	<var: #theFP type: #'char *'>
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentation>>branchIfInstanceOfBehavior:branches: (in category 'sista support') -----
  branchIfInstanceOfBehavior: classObj branches: branches
  	"Generate a branch if ReceiverResultReg is an instance of classObj, otherwise fall-
  	 through. Store the branch in branches and answer the number of branches generated."
+ 	<var: #branches type: #'AbstractInstruction **'>
  	self subclassResponsibility!

Item was changed:
  ----- Method: CogObjectRepresentation>>branchIfInstanceOfBehaviors:branches: (in category 'sista support') -----
  branchIfInstanceOfBehaviors: arrayObj branches: branches
  	"Generate a branch if ReceiverResultReg is an instance of any of the classes in arrayObj,
  	 otherwise fall-through. Store the branch in branches and answer the number of branches
  	 generated."
+ 	<var: #branches type: #'AbstractInstruction **'>
- 
  	self subclassResponsibility!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>branchIfInstanceOfBehavior:branches: (in category 'in-line cacheing') -----
  branchIfInstanceOfBehavior: classObj branches: branches
  	"Generate a branch if ReceiverResultReg is an instance of classObj, otherwise fall-
  	 through. Store the branch in branches and answer the number of branches generated."
+ 	<var: #branches type: #'AbstractInstruction **'>
- 	<var: #branches type: #'AbstractInstruction *'>
  	| jmpImmediate classIndex |
  	<var: #jmpImmediate type: #'AbstractInstruction *'>
  	classIndex := objectMemory classTagForClass: classObj.
  	cogit MoveR: ReceiverResultReg R: TempReg.
  	(objectMemory isImmediateClass: classObj)
  		ifTrue:
  			[classIndex = objectMemory smallIntegerTag ifTrue:
  				[jmpImmediate := self genJumpSmallIntegerInScratchReg: TempReg].
  			 classIndex = objectMemory characterTag ifTrue:
  				[jmpImmediate := self genJumpCharacterInScratchReg: TempReg].
  			 branches at: 0 put: jmpImmediate]
  		ifFalse:
  			[jmpImmediate := self genJumpImmediateInScratchReg: TempReg.
  			 self genGetClassIndexOfNonImm: ReceiverResultReg into: TempReg.
  			 self genCmpClassIndex: classIndex R: TempReg.
  			 branches at: 0 put: (cogit JumpZero: 0).
  			 jmpImmediate jmpTarget: cogit Label].
  	^1!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>branchIfInstanceOfBehaviors:branches: (in category 'in-line cacheing') -----
  branchIfInstanceOfBehaviors: arrayObj branches: branches
  	"Generate a branch if ReceiverResultReg is an instance of any of the classes in arrayObj,
  	 otherwise fall-through. Store the branch in branches and answer the number of branches
  	 generated."
+ 	<var: #branches type: #'AbstractInstruction **'>
- 
- 	<var: #branches type: #'AbstractInstruction *'>
  	| allImmediate noneImmediate immediateMask numNonImmediates classObj jmpNoMatch jmpImmediate branchIndex classIndex |
  	<var: #jmpNoMatch type: #'AbstractInstruction *'>
  	<var: #jmpImmediate type: #'AbstractInstruction *'>
  	branchIndex := 0.
  	"let me tell you all about it, let me falsify"
  	allImmediate := true. noneImmediate := true. immediateMask := 0. numNonImmediates := 0.
  	0 to: (objectMemory numSlotsOf: arrayObj) - 1 do:
  		[:i|
  		 classObj := objectMemory fetchPointer: i ofObject: arrayObj.
  		 (objectMemory isImmediateClass: classObj)
  			ifTrue:
  				[noneImmediate := false.
  				 immediateMask := immediateMask + (objectMemory classTagForClass: classObj)]
  			ifFalse:
  				[allImmediate := false.
  				 numNonImmediates := numNonImmediates + 1]].
  
  	noneImmediate ifTrue:
  		[cogit MoveR: ReceiverResultReg R: TempReg.
  		 jmpImmediate := self genJumpImmediateInScratchReg: TempReg.
  		 self genGetCompactClassIndexNonImmOf: ReceiverResultReg into: TempReg.
  		 0 to: (objectMemory numSlotsOf: arrayObj) - 1 do:
  			[:i|
  			 classObj := objectMemory fetchPointer: i ofObject: arrayObj.
  			 self genCmpClassIndex: (objectMemory classTagForClass: classObj) R: TempReg.
  			 branches at: branchIndex put: (cogit JumpZero: 0).
  			 branchIndex := branchIndex + 1].
  		 jmpImmediate jmpTarget: cogit Label].
  
  	allImmediate ifTrue:
  		[immediateMask = objectMemory tagMask
  			ifTrue:
  				[jmpImmediate := self genJumpImmediateInScratchReg: TempReg.
  				 branches at: branchIndex put: jmpImmediate.
  				 branchIndex := branchIndex + 1]
  			ifFalse:
  				[0 to: (objectMemory numSlotsOf: arrayObj) - 1 do:
  					[:i|
  					 cogit MoveR: ReceiverResultReg R: TempReg.
  					 classObj := objectMemory fetchPointer: i ofObject: arrayObj.
  					 classIndex := objectMemory classTagForClass: classObj.
  					 classIndex = objectMemory smallIntegerTag ifTrue:
  						[jmpImmediate := self genJumpSmallIntegerInScratchReg: TempReg].
  					 classIndex = objectMemory characterTag ifTrue:
  						[jmpImmediate := self genJumpCharacterInScratchReg: TempReg].
  					 branches at: branchIndex put: jmpImmediate.
  					 branchIndex := branchIndex + 1]]].
  
  	(allImmediate or: [noneImmediate]) ifFalse:
  		[cogit MoveR: ReceiverResultReg R: TempReg.
  		 jmpImmediate := self genJumpImmediateInScratchReg: TempReg.
  		 self genGetCompactClassIndexNonImmOf: ReceiverResultReg into: TempReg.
  		 0 to: (objectMemory numSlotsOf: arrayObj) - 1 do:
  			[:i|
  			 classObj := objectMemory fetchPointer: i ofObject: arrayObj.
  			 (objectMemory isImmediateClass: classObj) ifFalse:
  			 	[self genCmpClassIndex: (objectMemory classTagForClass: classObj) R: TempReg.
  				 branches at: branchIndex put: (cogit JumpZero: 0).
  				 branchIndex := branchIndex + 1]].
  		 jmpNoMatch := cogit Jump: 0.
  		 jmpImmediate jmpTarget: cogit Label.
  		 0 to: (objectMemory numSlotsOf: arrayObj) - 1 do:
  			[:i|
  			 classObj := objectMemory fetchPointer: i ofObject: arrayObj.
  			 (objectMemory isImmediateClass: classObj) ifTrue:
  			 	["first time through TempReg already contains tag pattern, so no need to reload it."
  				 branchIndex > numNonImmediates ifTrue:
  					[cogit MoveR: ReceiverResultReg R: TempReg].
  				 classIndex := objectMemory classTagForClass: classObj.
  				 classIndex = objectMemory smallIntegerTag ifTrue:
  					[jmpImmediate := self genJumpSmallIntegerInScratchReg: TempReg].
  				 classIndex = objectMemory characterTag ifTrue:
  					[jmpImmediate := self genJumpCharacterInScratchReg: TempReg].
  				 branches at: branchIndex put: jmpImmediate.
  				 branchIndex := branchIndex + 1]].
  		 jmpNoMatch jmpTarget: cogit Label].
  
  	self assert: branchIndex <= (objectMemory numSlotsOf: arrayObj).
  	^branchIndex!

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>branchIfInstanceOfBehavior:branches: (in category 'sista support') -----
  branchIfInstanceOfBehavior: classObj branches: branches
  	"Generate a branch if ReceiverResultReg is an instance of classObj, otherwise fall-
  	 through. Store the branch in branches and answer the number of branches generated."
+ 	<var: #branches type: #'AbstractInstruction **'>
- 	<var: #branches type: #'AbstractInstruction *'>
  	| jmpImmediate compactClassIndex |
  	<var: #jmpImmediate type: #'AbstractInstruction *'>
  	cogit MoveR: ReceiverResultReg R: TempReg.
  	jmpImmediate := self genJumpSmallIntegerInScratchReg: TempReg.
  	classObj = (objectMemory splObj: ClassSmallInteger) ifTrue:
  		[branches at: 0 put: jmpImmediate.
  		 ^1].
  	(compactClassIndex := objectMemory compactClassIndexOfClass: classObj) ~= 0
  		ifTrue:
  			[self genGetCompactClassIndexNonImmOf: ReceiverResultReg into: TempReg.
  			 cogit CmpCq: compactClassIndex R: TempReg]
  		ifFalse:
  			[self genGetClassObjectOfNonCompact: ReceiverResultReg into: TempReg.
  			 cogit
  				annotate: (cogit CmpCw: classObj R: TempReg)
  				objRef: classObj].
  	branches at: 0 put: (cogit JumpZero: 0).
  	^1!

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>branchIfInstanceOfBehaviors:branches: (in category 'sista support') -----
  branchIfInstanceOfBehaviors: arrayObj branches: branches
  	"Generate a branch if ReceiverResultReg is an instance of any of the classes in arrayObj,
  	 otherwise fall-through. Store the branch in branches and answer the number of branches
  	 generated."
+ 	<var: #branches type: #'AbstractInstruction **'>
- 
- 	<var: #branches type: #'AbstractInstruction *'>
  	| anImmediate allCompact noneCompact classObj jmpImmediate jmpCompact branchIndex |
  	<var: #jmpCompact type: #'AbstractInstruction *'>
  	<var: #jmpImmediate type: #'AbstractInstruction *'>
  	"let me tell you all about it, let me falsify"
  	anImmediate := false. allCompact := true. noneCompact := true.
  	0 to: (objectMemory numSlotsOf: arrayObj) - 1 do:
  		[:i|
  		 classObj := objectMemory fetchPointer: i ofObject: arrayObj.
  		 classObj = (objectMemory splObj: ClassSmallInteger)
  			ifTrue:
  				[anImmediate := true]
  			ifFalse:
  				[(objectMemory compactClassIndexOfClass: classObj) = 0
  					ifTrue: [allCompact := false]
  					ifFalse: [noneCompact := false]]].
  	cogit MoveR: ReceiverResultReg R: TempReg.
  	branchIndex := 0.
  	jmpImmediate := self genJumpSmallIntegerInScratchReg: TempReg.
  	self genGetCompactClassIndexNonImmOf: ReceiverResultReg into: TempReg.
  	noneCompact
  		ifTrue:
  			[cogit CmpCq: 0 R: TempReg.
  			 jmpCompact := cogit JumpNonZero: 0]
  		ifFalse:
  			[0 to: (objectMemory numSlotsOf: arrayObj) - 1 do:
  				[:i| | compactClassIndex |
  				 classObj := objectMemory fetchPointer: i ofObject: arrayObj.
  				 (classObj ~= (objectMemory splObj: ClassSmallInteger)
  				  and: [(compactClassIndex := objectMemory compactClassIndexOfClass: classObj) ~= 0]) ifTrue:
  					[cogit CmpCq: compactClassIndex R: TempReg.
  					 branches at: branchIndex put: (cogit JumpZero: 0).
  					 branchIndex := branchIndex + 1]]].
  	allCompact ifFalse:
  		[self genGetClassObjectOfNonCompact: ReceiverResultReg into: TempReg.
  		 0 to: (objectMemory numSlotsOf: arrayObj) - 1 do:
  			[:i|
  			 classObj := objectMemory fetchPointer: i ofObject: arrayObj.
  			 (classObj ~= (objectMemory splObj: ClassSmallInteger)
  			  and: [(objectMemory compactClassIndexOfClass: classObj) = 0]) ifTrue:
  				[cogit
  					annotate: (cogit CmpCw: classObj R: TempReg)
  					objRef: classObj.
  				 branches at: branchIndex put: (cogit JumpZero: 0).
  				 branchIndex := branchIndex + 1]]].
  	"Either succeed or fail on the immediate test."
  	anImmediate
  		ifTrue: [branches at: branchIndex put: jmpImmediate.
  				branchIndex := branchIndex + 1]
  		ifFalse: [jmpImmediate jmpTarget: cogit Label].
  	noneCompact ifTrue:
  		[jmpCompact jmpTarget: cogit Label].
  	self assert: branchIndex = (objectMemory numSlotsOf: arrayObj).
  	^branchIndex!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveQuo (in category 'arithmetic integer primitives') -----
  primitiveQuo
  	"Rounds negative results towards zero."
  	| integerRcvr integerArg integerResult |
  	integerRcvr := self stackIntegerValue: 1.
  	integerArg := self stackIntegerValue: 0.
  	self success: integerArg ~= 0.
+ 	self successful ifTrue:
+ 		[integerResult := self quot: integerRcvr ient: integerArg].
- 	self successful ifTrue: [
- 		integerRcvr > 0 ifTrue: [
- 			integerArg > 0 ifTrue: [
- 				integerResult := integerRcvr // integerArg.
- 			] ifFalse: [
- 				integerResult := 0 - (integerRcvr // (0 - integerArg)).
- 			].
- 		] ifFalse: [
- 			integerArg > 0 ifTrue: [
- 				integerResult := 0 - ((0 - integerRcvr) // integerArg).
- 			] ifFalse: [
- 				integerResult := (0 - integerRcvr) // (0 - integerArg).
- 			].
- 		]].
  	self pop2AndPushIntegerIfOK: integerResult!

Item was added:
+ ----- Method: InterpreterPrimitives>>quot:ient: (in category 'arithmetic integer primitives') -----
+ quot: integerRcvr ient: integerArg
+ 	"See Number>>#quo:.  Rounds results towards zero."
+ 	<inline: true>
+ 	^integerRcvr > 0
+ 		ifTrue:
+ 			[integerArg > 0
+ 				ifTrue: [integerRcvr // integerArg]
+ 				ifFalse: [0 - (integerRcvr // (0 - integerArg))]]
+ 		ifFalse:
+ 			[integerArg > 0
+ 				ifTrue: [0 - ((0 - integerRcvr) // integerArg)]
+ 				ifFalse: [(0 - integerRcvr) // (0 - integerArg)]]!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genCallPrimitiveBytecode (in category 'bytecode generators') -----
+ genCallPrimitiveBytecode
+ 	"SistaV1: 248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution."
+ 	"This makes sense only for the optimizing JITs"
+ 	^EncounteredUnknownBytecode!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtTrapIfNotInstanceOfBehaviorsBytecode (in category 'bytecode generators') -----
  genExtTrapIfNotInstanceOfBehaviorsBytecode
  	"SistaV1: *	236		11101100	iiiiiiii		Trap If Not Instance Of Behavior/Array Of Behavior #iiiiiiii (+ Extend A * 256, where Extend A >= 0)"
+ 	"This really only makes sense for the optimizing JITs"
- 	"THis realy makes sense only for the optimizing JITs"
  	^EncounteredUnknownBytecode!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genExtTrapIfNotInstanceOfBehaviorsBytecode (in category 'bytecode generators') -----
  genExtTrapIfNotInstanceOfBehaviorsBytecode
  	"SistaV1: *	236		11101100	iiiiiiii		Trap If Not Instance Of Behavior/Array Of Behavior #iiiiiiii (+ Extend A * 256, where Extend A >= 0)"
  	| reg litIndex literal branches label numBranches |
  	<var: #branches type: #'AbstractInstruction **'>
  	reg := self ssStorePop: true toPreferredReg: ReceiverResultReg.
  	reg ~= ReceiverResultReg ifTrue:
  		[self MoveR: reg R: ReceiverResultReg].
  	optStatus isReceiverResultRegLive: false.
  	litIndex := extA * 256 + byte1.
  	extA := 0.
  	literal := self getLiteral: litIndex.
  	"Allow an extra branch for Spur, which may have two tag patterns for SmallInteger"
  	numBranches := (objectMemory isArrayNonImm: literal)
  						ifTrue: [(objectMemory numSlotsOf: literal) + 1]
  						ifFalse: [2].
+ 	branches := self alloca: numBranches type: (self cCode: [#'AbstractInstruction *'] inSmalltalk: [backEnd class]).
- 	branches := self alloca: numBranches type: (self cCoerceSimple: CogAbstractInstruction to: #'AbstractInstruction *').
  	numBranches := (objectMemory isArrayNonImm: literal)
  						ifTrue: [objectRepresentation branchIfInstanceOfBehaviors: literal branches: branches]
  						ifFalse: [objectRepresentation branchIfInstanceOfBehavior: literal branches: branches].
  	"Only flush the stack if the class trap traps.  Use ssFlushNoUpdateTo: so we continue compiling as if
  	 the stack had not been flushed.  Control does not return after the ceClassTrapTrampoline call."
  	self ssFlushNoUpdateTo: simStackPtr.
  	self CallRT: ceClassTrapTrampoline.
  	label := self Label.
  	0 to: numBranches - 1 do:
  		[:i|
  		(branches at: i) jmpTarget: label].
  	^0!

Item was changed:
  ----- Method: StackInterpreter>>inlinePrimitiveBytecode: (in category 'miscellaneous bytecodes') -----
(excessive size, no diff calculated)



More information about the Vm-dev mailing list