[Vm-dev] VM Maker: VMMaker.oscog-cb.1201.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Apr 16 19:27:12 UTC 2015


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

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

Name: VMMaker.oscog-cb.1201
Author: cb
Time: 16 April 2015, 12:25:27.512 pm
UUID: f8ff87ac-4da4-47b4-b2ea-17ff99caf18a
Ancestors: VMMaker.oscog-eem.1200

Replace bytecode trapIfNotInstanceOf by jumpIfNotInstanceOfOrPop.

Rewrote the JIT logic for traps to be able to write trap trampolines calls at the end of the cogMethod.

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

Item was removed:
- ----- 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 removed:
- ----- 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 added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>allImmediate:branchIf:notInstanceOfBehaviors:target: (in category 'sista support') -----
+ allImmediate: immediateMask branchIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp
+ 	| jmpImmediate |
+ 	< inline: true>	
+ 	self assert: immediateMask = objectMemory tagMask.
+ 	cogit MoveR: reg R: TempReg.
+ 	jmpImmediate := self genJumpNotImmediateInScratchReg: TempReg.
+ 	jmpImmediate jmpTarget: targetFixUp.!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>branch2CasesIf:notInstanceOfBehaviors:target: (in category 'sista support') -----
+ branch2CasesIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp
+ 	"nothing to do, 2 immediates so all immediates are allowed"
+ 	<inline: true>!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>branchIf:hasNotImmediateTag:target: (in category 'sista support') -----
+ branchIf: reg hasNotImmediateTag: classIndex target: targetFixUp
+ 	| jmpImmediate|
+ 	<inline: true>
+ 	cogit MoveR: reg R: TempReg.
+ 	classIndex = objectMemory smallIntegerTag ifTrue:
+ 		[jmpImmediate := self genJumpNotSmallIntegerInScratchReg: TempReg].
+ 	classIndex = objectMemory characterTag ifTrue:
+ 		[jmpImmediate := self genJumpNotCharacterInScratchReg: TempReg].
+ 	jmpImmediate jmpTarget: targetFixUp!

Item was removed:
- ----- 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 **'>
- 	| 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 removed:
- ----- 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 **'>
- 	| 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 added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>allImmediate:branchIf:notInstanceOfBehaviors:target: (in category 'sista support') -----
+ allImmediate: immediateMask branchIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp
+ 	| incorrectTag tag1 tag2 |
+ 	< inline: true>		
+ 	cogit MoveR: reg R: TempReg.
+ 	(self genJumpNotImmediateInScratchReg: TempReg) jmpTarget: targetFixUp. 
+ 	immediateMask = objectMemory tagMask ifFalse: 
+ 		[ "TempReg holds the rcvr tag"
+ 		"In this case one immediate tag out of the three is not present in arrayObj. 
+ 		We look for it, and generate a jump to the fixup if the rcvr tag matches"
+ 		tag1 := objectMemory classTagForClass: (objectMemory fetchPointer: 0 ofObject: arrayObj).
+ 		tag2 := objectMemory classTagForClass: (objectMemory fetchPointer: 1 ofObject: arrayObj).
+ 		incorrectTag :=  self fetchImmediateTagOtherThanTag1: tag1 tag2: tag2.
+ 		cogit CmpCq: incorrectTag R: TempReg.
+ 		cogit JumpZero: targetFixUp ].!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>branch2CasesIf:notInstanceOfBehaviors:target: (in category 'sista support') -----
+ branch2CasesIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp
+ 	"Only 2 immediate type allowed out of the three. Look for the third and jump to target fixup if it's the third.
+ 	TempReg currently holds the rcvr tag and the receiver is immediate."
+ 	
+ 	| incorrectTag classObj tag1 tag2 |
+ 	< inline: true>		
+ 	
+ 	"look for the 2 allowed tags"
+ 	0 to: (objectMemory numSlotsOf: arrayObj) - 1 do:
+ 		[:i|
+ 		 classObj := objectMemory fetchPointer: i ofObject: arrayObj.
+ 		 (objectMemory isImmediateClass: classObj)
+ 			ifTrue: [ tag1
+ 				ifNil: [tag1 := objectMemory classTagForClass: classObj ]
+ 				ifNotNil: [tag2 := objectMemory classTagForClass: classObj ] ] ].
+ 	
+ 	incorrectTag := self fetchImmediateTagOtherThanTag1: tag1 tag2: tag2.
+ 	cogit CmpCq: incorrectTag R: TempReg.
+ 	cogit JumpZero: targetFixUp.
+ 	!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>branchIf:hasNotImmediateTag:target: (in category 'sista support') -----
+ branchIf: reg hasNotImmediateTag: classIndex target: targetFixUp
+ 	| jmpImmediate|
+ 	<inline: true>
+ 	cogit MoveR: reg R: TempReg.
+ 	classIndex = objectMemory smallIntegerTag ifTrue:
+ 		[jmpImmediate := self genJumpNotSmallIntegerInScratchReg: TempReg].
+ 	classIndex = objectMemory characterTag ifTrue:
+ 		[jmpImmediate := self genJumpNotCharacterInScratchReg: TempReg].
+ 	classIndex = objectMemory smallFloatTag ifTrue:
+ 		[jmpImmediate := self genJumpNotSmallFloatInScratchReg: TempReg].
+ 	jmpImmediate jmpTarget: targetFixUp!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>fetchImmediateTagOtherThanTag1:tag2: (in category 'sista support') -----
+ fetchImmediateTagOtherThanTag1: tag1 tag2: tag2
+ 	"Answers the immediate tag which is not tag1 nor tag2, usually Character."
+ 	<inline: true>
+ 	(tag1 = objectMemory characterTag or: [ tag2 = objectMemory characterTag ]) ifFalse: 
+ 		[ ^ objectMemory characterTag ].
+ 	(tag1 = objectMemory smallIntegerTag or: [ tag2 = objectMemory smallIntegerTag ]) ifFalse: 
+ 		[ ^ objectMemory smallIntegerTag ].
+ 	^ objectMemory smallFloatTag!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>branchIf:notInstanceOfBehavior:target: (in category 'sista support') -----
+ branchIf: reg notInstanceOfBehavior: classObj target: targetFixUp
+ 	"Generate a branch if reg is an instance of classObj, otherwise fall-
+ 	 through. Cannot change the value of reg (may be used afterwards)."
+ 	| classIndex |
+ 	<inline: true>
+ 	<var: #jmpImmediate type: #'AbstractInstruction *'>
+ 	classIndex := objectMemory classTagForClass: classObj.
+ 	(objectMemory isImmediateClass: classObj)
+ 		ifTrue:
+ 			[self branchIf: reg hasNotImmediateTag: classIndex target: targetFixUp ]
+ 		ifFalse:
+ 			[cogit MoveR: reg R: TempReg.
+ 			(self genJumpImmediateInScratchReg: TempReg) jmpTarget: targetFixUp.
+ 			 self genGetClassIndexOfNonImm: reg into: TempReg.
+ 			 self genCmpClassIndex: classIndex R: TempReg.
+ 			 cogit JumpNonZero: targetFixUp ].
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>branchIf:notInstanceOfBehaviors:target: (in category 'sista support') -----
+ branchIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp
+ 	"Generate a branch if reg is an instance of any of the classes in arrayObj,
+ 	 otherwise fall-through. reg should not be edited."
+ 	
+ 	| allImmediate noneImmediate immediateMask numNonImmediates classObj |
+ 	<inline: true>
+ 	
+ 	"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: [ ^ self noneImmediateBranchIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp ].
+ 
+ 	allImmediate ifTrue: [ ^ self allImmediate: immediateMask branchIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp ].
+ 
+ 	^ self mixed: numNonImmediates branchIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genJumpNotImmediateInScratchReg: (in category 'compile abstract instructions') -----
+ genJumpNotImmediateInScratchReg: aRegister
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	cogit AndCq: objectMemory tagMask R: aRegister.
+ 	^cogit JumpZero: 0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>mixed:branchIf:notInstanceOfBehaviors:target: (in category 'sista support') -----
+ mixed: numNonImmediates branchIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp
+ 	| jmpImmediate jumps label numCases classObj index |
+ 	numCases := objectMemory numSlotsOf: arrayObj.
+ 	cogit MoveR: reg R: TempReg.
+ 	jmpImmediate := self genJumpImmediateInScratchReg: TempReg.
+ 	
+ 	"Rcvr is non immediate"
+ 	jumps := self alloca: numNonImmediates type: (self cCode: [#'AbstractInstruction *'] inSmalltalk: [cogit backEnd class])..
+ 	self genGetClassIndexOfNonImm: reg into: TempReg.
+ 	index := 0.
+ 	0 to: numCases - 1 do:
+ 		[:i|
+ 			classObj := objectMemory fetchPointer: i ofObject: arrayObj.
+ 			(objectMemory isImmediateClass: classObj) ifFalse: [
+ 				self genCmpClassIndex: (objectMemory classTagForClass: classObj) R: TempReg.
+ 				jumps at: index put: (cogit JumpZero: 0).
+ 				index := index + 1 ] ].
+ 	cogit Jump: targetFixUp.
+ 	
+ 	"Rcvr is immediate"
+ 	jmpImmediate jmpTarget: cogit Label.
+ 	numCases - numNonImmediates "num Immediates allowed"
+ 		caseOf:
+ 		{[ 1 ] -> [ "1 immediate allowed. jump to targetFixUp if the rcvr is not this immediate"
+ 			0 to: numCases - 1 do:
+ 				[ :j |
+ 				classObj := objectMemory fetchPointer: j ofObject: arrayObj.
+ 				(objectMemory isImmediateClass: classObj) ifTrue: [
+ 					self branchIf: reg hasNotImmediateTag: (objectMemory classTagForClass: classObj) target: targetFixUp ] ] ] .
+ 		[ 2 ] -> [ "2 immediates allowed. On 32 bits nothing to do, all immediate are allowed, on 64 bits generates the jump to fixup for the third tag"
+ 				self branch2CasesIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp ] .
+ 		[ 3 ] -> [ "nothing to do, all immediates are allowed." ] }.
+ 	
+ 	label := self Label.
+ 	0 to: numNonImmediates - 1 do: [:i |
+ 		(jumps at: i) jmpTarget: label ].
+ 	
+ 	^ 0
+ 		!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>noneImmediateBranchIf:notInstanceOfBehaviors:target: (in category 'sista support') -----
+ noneImmediateBranchIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp
+ 	"All classes in arrayObj are not immediate"
+ 	<inline: true>
+ 	| label numJumps jumps classObj |
+ 	cogit MoveR: reg R: TempReg.
+ 	jumps := self alloca: (objectMemory numSlotsOf: arrayObj) type: (self cCode: [#'AbstractInstruction *'] inSmalltalk: [cogit backEnd class])..
+ 	(self genJumpImmediateInScratchReg: TempReg) jmpTarget: targetFixUp.
+ 	self genGetClassIndexOfNonImm: reg into: TempReg.
+ 	0 to: (numJumps := objectMemory numSlotsOf: arrayObj) - 1 do:
+ 		[:i|
+ 		 classObj := objectMemory fetchPointer: i ofObject: arrayObj.
+ 		 self genCmpClassIndex: (objectMemory classTagForClass: classObj) R: TempReg.
+ 		jumps at: i put: (cogit JumpZero: 0) ].
+ 	cogit Jump: targetFixUp.
+ 	label := self Label.
+ 	0 to: numJumps do: [:i |
+ 		(jumps at: i) jmpTarget: label ].
+ 	!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializeBytecodeTableForSistaV1 (in category 'class initialization') -----
  initializeBytecodeTableForSistaV1
  	"SimpleStackBasedCogit initializeBytecodeTableForSistaV1"
  
  	BytecodeSetHasDirectedSuperSend := true.
  	FirstSpecialSelector := 96.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		"1 byte bytecodes"
  		"pushes"
  		(1    0   15 genPushReceiverVariableBytecode)
  		(1  16   31 genPushLiteralVariable16CasesBytecode	needsFrameNever: 1)
  		(1  32   63 genPushLiteralConstantBytecode			needsFrameNever: 1)
  		(1  64   75 genPushTemporaryVariableBytecode)
  		(1  76   76 genPushReceiverBytecode)
  		(1  77   77 genPushConstantTrueBytecode				needsFrameNever: 1)
  		(1  78   78 genPushConstantFalseBytecode			needsFrameNever: 1)
  		(1  79   79 genPushConstantNilBytecode				needsFrameNever: 1)
  		(1  80   80 genPushConstantZeroBytecode				needsFrameNever: 1)
  		(1  81   81 genPushConstantOneBytecode				needsFrameNever: 1)
  		(1  82   82 genExtPushPseudoVariable)
  		(1  83   83 duplicateTopBytecode						needsFrameNever: 1)
  
  		(1  84   87 unknownBytecode)
  
  		"returns"
  		(1  88   88 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  89   89 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  90   90 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  91   91 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  92   92 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1  93   93 genReturnNilFromBlock			return needsFrameNever: -1)
  		(1  94   94 genReturnTopFromBlock		return needsFrameNever: -1)
  		(1  95   95 genExtNopBytecode			needsFrameNever: 0)
  
  		"sends"
  		(1   96 117 genSpecialSelectorSend isMapped) "#+ #- #< #> #<= #>= #= #~= #* #/ #\\ #@ #bitShift: #// #bitAnd: #bitOr: #at: #at:put: #size #next #nextPut: #atEnd"
  		(1 118 118 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 119 119 genSpecialSelectorClass needsFrameNever: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 120 127 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  
  		(1 128 143 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 144 159 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 160 175 genSendLiteralSelector2ArgsBytecode isMapped)
  
  		"jumps"
  		(1 176 183 genShortUnconditionalJump	branch v3:ShortForward:Branch:Distance:)
  		(1 184 191 genShortJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  		(1 192 199 genShortJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  
  		"stores"
  		(1 200 207 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 208 215 genStoreAndPopTemporaryVariableBytecode)
  
  		(1 216 216 genPopStackBytecode needsFrameNever: -1)
  
  		(1 217 217 genUnconditionalTrapBytecode isMapped)
  
  		(1 218 223 unknownBytecode)
  
  		"2 byte bytecodes"
  		(2 224 224 extABytecode extension)
  		(2 225 225 extBBytecode extension)
  
  		"pushes"
  		(2 226 226 genExtPushReceiverVariableBytecode)		"Needs a frame for context inst var access"
  		(2 227 227 genExtPushLiteralVariableBytecode		needsFrameNever: 1)
  		(2 228 228 genExtPushLiteralBytecode					needsFrameNever: 1)
  		(2 229 229 genLongPushTemporaryVariableBytecode)
  		(2 230 230 genPushClosureTempsBytecode)
  		(2 231 231 genPushNewArrayBytecode)
  		(2 232 232 genExtPushIntegerBytecode				needsFrameNever: 1)
  		(2 233 233 genExtPushCharacterBytecode				needsFrameNever: 1)
  
  		"returns"
  		"sends"
  		(2 234 234 genExtSendBytecode isMapped)
  		(2 235 235 genExtSendSuperBytecode isMapped)
  
  		"sista bytecodes"
+ 		(2 236 236 unknownBytecode)
- 		(2 236 236 genExtTrapIfNotInstanceOfBehaviorsBytecode isMapped)
  
  		"jumps"
  		(2 237 237 genExtUnconditionalJump	branch isMapped "because of interrupt check" v4:Long:Branch:Distance:)
  		(2 238 238 genExtJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  		(2 239 239 genExtJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  
  		"stores"
  		(2 240 240 genExtStoreAndPopReceiverVariableBytecode)
  		(2 241 241 genExtStoreAndPopLiteralVariableBytecode)
  		(2 242 242 genLongStoreAndPopTemporaryVariableBytecode)
  		(2 243 243 genExtStoreReceiverVariableBytecode)
  		(2 244 244 genExtStoreLiteralVariableBytecode)
  		(2 245 245 genLongStoreTemporaryVariableBytecode)
  
  		(2 246 247	unknownBytecode)
  
  		"3 byte bytecodes"
  		(3 248 248 genCallPrimitiveBytecode)
  		(3 249 249 unknownBytecode) "reserved for Push Float"
  		(3 250 250 genExtPushClosureBytecode block v4:Block:Code:Size:)
  		(3 251 251 genPushRemoteTempLongBytecode)
  		(3 252 252 genStoreRemoteTempLongBytecode)
  		(3 253 253 genStoreAndPopRemoteTempLongBytecode)
  
+ 		(3 254 254	genExtJumpIfNotInstanceOfBehaviorsOrPopBytecode)
+ 			
+ 		(3 255 255	unknownBytecode))!
- 		(3 254 255	unknownBytecode))!

Item was added:
+ ----- Method: SistaStackToRegisterMappingCogit>>genExtJumpIfNotInstanceOfBehaviorsOrPopBytecode (in category 'bytecode generators') -----
+ genExtJumpIfNotInstanceOfBehaviorsOrPopBytecode
+ 	"SistaV1: *	254		11111110	kkkkkkkk	jjjjjjjj		branch If Not Instance Of Behavior/Array Of Behavior kkkkkkkk (+ Extend A * 256, where Extend A >= 0) distance jjjjjjjj (+ Extend B * 256, where Extend B >= 0)"
+ 								
+ 	| reg literal distance targetFixUp |
+ 	
+ 	reg := self allocateOneRegister.
+ 	self ssTop popToReg: reg.
+ 	
+ 	literal := self getLiteral: (extA * 256 + byte1).
+ 	extA := 0.
+ 	distance := extB * 256 + byte2.
+ 	extB := 0.
+ 	
+ 	targetFixUp := (self ensureFixupAt: bytecodePC + 3 + distance - initialPC) asUnsignedInteger.
+ 		
+ 	(objectMemory isArrayNonImm: literal)
+ 		ifTrue: [objectRepresentation branchIf: reg notInstanceOfBehaviors: literal target: targetFixUp]
+ 		ifFalse: [objectRepresentation branchIf: reg notInstanceOfBehavior: literal target: targetFixUp].
+ 						
+ 	self genPopStackBytecode.
+ 	
+ 	^0!

Item was removed:
- ----- 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]).
- 	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: ceTrapTrampoline.
- 	label := self Label.
- 	self annotateBytecode: label.
- 	0 to: numBranches - 1 do:
- 		[:i|
- 		(branches at: i) jmpTarget: label].
- 	^0!

Item was changed:
  ----- Method: StackInterpreter class>>initializeBytecodeTableForSistaV1 (in category 'initialization') -----
  initializeBytecodeTableForSistaV1
  	"See e.g. the cass comment for EncoderForSistaV1"
  	"StackInterpreter initializeBytecodeTableForSistaV1"
  	"Note: This table will be used to generate a C switch statement."
  
  	BytecodeTable := Array new: 256.
  	BytecodeEncoderClassName := #EncoderForSistaV1.
  	BytecodeSetHasDirectedSuperSend := true.
  
  	self table: BytecodeTable from:
  	#(	"1 byte bytecodes"
  		(   0  15 pushReceiverVariableBytecode)
  		( 16  31 pushLiteralVariable16CasesBytecode)
  		( 32  63 pushLiteralConstantBytecode)
  		( 64  75 pushTemporaryVariableBytecode)
  		( 76	 pushReceiverBytecode)
  		( 77	 pushConstantTrueBytecode)
  		( 78	 pushConstantFalseBytecode)
  		( 79	 pushConstantNilBytecode)
  		( 80	 pushConstantZeroBytecode)
  		( 81	 pushConstantOneBytecode)
  		( 82	 extPushPseudoVariable)
  		( 83	 duplicateTopBytecode)
  	
  		( 84 87	unknownBytecode)
  		( 88	returnReceiver)
  		( 89	returnTrue)
  		( 90	returnFalse)
  		( 91	returnNil)
  		( 92	returnTopFromMethod)
  		( 93	returnNilFromBlock)
  		( 94	returnTopFromBlock)
  		( 95	extNopBytecode)
  
  		( 96	 bytecodePrimAdd)
  		( 97	 bytecodePrimSubtract)
  		( 98	 bytecodePrimLessThanSistaV1) "for booleanCheatSistaV1:"
  		( 99	 bytecodePrimGreaterThanSistaV1) "for booleanCheatSistaV1:"
  		(100	 bytecodePrimLessOrEqualSistaV1) "for booleanCheatSistaV1:"
  		(101	 bytecodePrimGreaterOrEqualSistaV1) "for booleanCheatSistaV1:"
  		(102	 bytecodePrimEqualSistaV1) "for booleanCheatSistaV1:"
  		(103	 bytecodePrimNotEqualSistaV1) "for booleanCheatSistaV1:"
  		(104	 bytecodePrimMultiply)
  		(105	 bytecodePrimDivide)
  		(106	 bytecodePrimMod)
  		(107	 bytecodePrimMakePoint)
  		(108	 bytecodePrimBitShift)
  		(109	 bytecodePrimDiv)
  		(110	 bytecodePrimBitAnd)
  		(111	 bytecodePrimBitOr)
  
  		(112	 bytecodePrimAt)
  		(113	 bytecodePrimAtPut)
  		(114	 bytecodePrimSize)
  		(115	 bytecodePrimNext)		 "i.e. a 0 arg special selector"
  		(116	 bytecodePrimNextPut)		 "i.e. a 1 arg special selector"
  		(117	 bytecodePrimAtEnd)
  		(118	 bytecodePrimIdenticalSistaV1) "for booleanCheatSistaV1:"
  		(119	 bytecodePrimClass)
  		(120	 bytecodePrimSpecialSelector24) "was blockCopy:"
  		(121	 bytecodePrimValue)
  		(122	 bytecodePrimValueWithArg)
  		(123	 bytecodePrimDo)			"i.e. a 1 arg special selector"
  		(124	 bytecodePrimNew)			"i.e. a 0 arg special selector"
  		(125	 bytecodePrimNewWithArg)	"i.e. a 1 arg special selector"
  		(126	 bytecodePrimPointX)		"i.e. a 0 arg special selector"
  		(127	 bytecodePrimPointY)		"i.e. a 0 arg special selector"
  
  		(128 143	sendLiteralSelector0ArgsBytecode)
  		(144 159	sendLiteralSelector1ArgBytecode)
  		(160 175	sendLiteralSelector2ArgsBytecode)
  
  		(176 183	shortUnconditionalJump)
  		(184 191	shortConditionalJumpTrue)
  		(192 199	shortConditionalJumpFalse)
  	
  		(200 207	storeAndPopReceiverVariableBytecode)
  		(208 215	storeAndPopTemporaryVariableBytecode)
  		(216		popStackBytecode)
  		(217		unconditionnalTrapBytecode)
  
  		(218 223	unknownBytecode)
  
  		"2 byte bytecodes"
  		(224		extABytecode)
  		(225		extBBytecode)
  
  		(226		extPushReceiverVariableBytecode)
  		(227		extPushLiteralVariableBytecode)
  		(228		extPushLiteralBytecode)
  		(229		longPushTemporaryVariableBytecode)
  		(230		pushClosureTempsBytecode)
  		(231		pushNewArrayBytecode)
  		(232		extPushIntegerBytecode)
  		(233		extPushCharacterBytecode)
  
  		(234		extSendBytecode)
  		(235		extSendSuperBytecode)
  
+ 		(236		unknownBytecode)
- 		(236		extTrapIfNotInstanceOfBehaviorsBytecode)
  
  		(237		extUnconditionalJump)
  		(238		extJumpIfTrue)
  		(239		extJumpIfFalse)
  
  		(240		extStoreAndPopReceiverVariableBytecode)
  		(241		extStoreAndPopLiteralVariableBytecode)
  		(242		longStoreAndPopTemporaryVariableBytecode)
  
  		(243		extStoreReceiverVariableBytecode)
  		(244		extStoreLiteralVariableBytecode)
  		(245		longStoreTemporaryVariableBytecode)
  
  		(246 247	unknownBytecode)
  
  		"3 byte bytecodes"
  		(248		callPrimitiveBytecode)
  		(249		unknownBytecode) "reserved for Push Float"
  
  		(250		extPushClosureBytecode)
  		(251		pushRemoteTempLongBytecode)
  		(252		storeRemoteTempLongBytecode)
  		(253		storeAndPopRemoteTempLongBytecode)
+ 				
+ 		(254		extJumpIfNotInstanceOfBehaviorsOrPopBytecode)
  
+ 		(255		unknownBytecode)
- 		(254 255	unknownBytecode)
  	)!

Item was added:
+ ----- Method: StackInterpreter>>extJumpIfNotInstanceOfBehaviorsOrPopBytecode (in category 'sista bytecodes') -----
+ extJumpIfNotInstanceOfBehaviorsOrPopBytecode
+ 	"254		11111110	kkkkkkkk	jjjjjjjj		branch If Not Instance Of Behavior/Array Of Behavior kkkkkkkk (+ Extend A * 256, where Extend A >= 0) distance jjjjjjjj (+ Extend B * 256, where Extend B >= 0)"
+ 	| tosClassTag literal distance |
+ 	tosClassTag := objectMemory fetchClassTagOf: self internalStackTop.
+ 	literal := self literal: extA << 8 + self fetchByte.
+ 	distance := extB << 8 + self fetchByte.
+ 	extA := 0.
+ 	extB := 0.
+ 	(objectMemory isArrayNonImm: literal)
+ 		ifTrue:
+ 			[| i |
+ 			 i := (objectMemory numSlotsOf: literal) asInteger.
+ 			 [(i := i -1) < 0
+ 			  or: [tosClassTag = (objectMemory rawClassTagForClass: (objectMemory fetchPointer: i ofObject: literal))]] whileTrue.
+ 			 i < 0 ifTrue:
+ 				[localIP := localIP + distance.
+ 				^ self fetchNextBytecode]]
+ 		ifFalse:
+ 			[tosClassTag ~= (objectMemory rawClassTagForClass: literal) ifTrue:
+ 				[localIP := localIP + distance.
+ 				^ self fetchNextBytecode]].
+ 	self internalPopStack.
+ 	self fetchNextBytecode!

Item was changed:
  ----- Method: StackInterpreter>>respondToSistaTrap (in category 'sista bytecodes') -----
  respondToSistaTrap
  	| ourContext tos |
+ 	<sharedCodeInCase: #unconditionnalTrapBytecode>
- 	<sharedCodeInCase: #extTrapIfNotInstanceOfBehaviorsBytecode>
  	messageSelector := objectMemory splObj: SelectorSistaTrap.
  	tos := self internalPopStack.
  	ourContext := self ensureFrameIsMarried: localFP SP: localSP.
  	messageSelector = objectMemory nilObject ifTrue:
  		[self error: 'Sista trap but no trap selector installed'].
  	self internalPush: ourContext.
  	self internalPush: tos.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForSistaV1 (in category 'class initialization') -----
  initializeBytecodeTableForSistaV1
  	"StackToRegisterMappingCogit initializeBytecodeTableForSistaV1"
  
  	numPushNilsFunction := #sistaV1:Num:Push:Nils:.
  	pushNilSizeFunction := #sistaV1PushNilSize:numInitialNils:.
  	BytecodeSetHasDirectedSuperSend := true.
  	FirstSpecialSelector := 96.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		"1 byte bytecodes"
  		"pushes"
  		(1    0   15 genPushReceiverVariableBytecode			needsFrameNever: 1)
  		(1  16   31 genPushLitVarDirSup16CasesBytecode	needsFrameNever: 1)
  		(1  32   63 genPushLiteralConstantBytecode			needsFrameNever: 1)
  		(1  64   75 genPushTemporaryVariableBytecode		needsFrameIfMod16GENumArgs: 1)
  		(1  76   76 genPushReceiverBytecode					needsFrameNever: 1)
  		(1  77   77 genPushConstantTrueBytecode				needsFrameNever: 1)
  		(1  78   78 genPushConstantFalseBytecode			needsFrameNever: 1)
  		(1  79   79 genPushConstantNilBytecode				needsFrameNever: 1)
  		(1  80   80 genPushConstantZeroBytecode				needsFrameNever: 1)
  		(1  81   81 genPushConstantOneBytecode				needsFrameNever: 1)
  		(1  82   82 genExtPushPseudoVariable)
  		(1  83   83 duplicateTopBytecode						needsFrameNever: 1)
  
  		(1  84   87 unknownBytecode)
  
  		"returns"
  		(1  88   88 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  89   89 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  90   90 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  91   91 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  92   92 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1  93   93 genReturnNilFromBlock			return needsFrameNever: -1)
  		(1  94   94 genReturnTopFromBlock		return needsFrameNever: -1)
  		(1  95   95 genExtNopBytecode			needsFrameNever: 0)
  
  		"sends"
  		(1  96   96 genSpecialSelectorArithmetic isMapped AddRR)
  		(1  97   97 genSpecialSelectorArithmetic isMapped SubRR)
  		(1  98   98 genSpecialSelectorComparison isMapped JumpLess)
  		(1  99   99 genSpecialSelectorComparison isMapped JumpGreater)
  		(1 100 100 genSpecialSelectorComparison isMapped JumpLessOrEqual)
  		(1 101 101 genSpecialSelectorComparison isMapped JumpGreaterOrEqual)
  		(1 102 102 genSpecialSelectorComparison isMapped JumpZero)
  		(1 103 103 genSpecialSelectorComparison isMapped JumpNonZero)
  		(1 104 109 genSpecialSelectorSend isMapped)	 " #* #/ #\\ #@ #bitShift: //"
  		(1 110 110 genSpecialSelectorArithmetic isMapped AndRR)
  		(1 111 111 genSpecialSelectorArithmetic isMapped OrRR)
  		(1 112 117 genSpecialSelectorSend isMapped) "#at: #at:put: #size #next #nextPut: #atEnd"
  		(1 118 118 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 119 119 genSpecialSelectorClass needsFrameIfStackGreaterThanOne: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 120 127 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  
  		(1 128 143 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 144 159 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 160 175 genSendLiteralSelector2ArgsBytecode isMapped)
  
  		"jumps"
  		(1 176 183 genShortUnconditionalJump	branch v3:ShortForward:Branch:Distance:)
  		(1 184 191 genShortJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  		(1 192 199 genShortJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  
  		"stores"
  		(1 200 207 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 208 215 genStoreAndPopTemporaryVariableBytecode)
  
  		(1 216 216 genPopStackBytecode needsFrameNever: -1)
  
  		(1 217 217 genUnconditionalTrapBytecode isMapped)
  
  		(1 218 223 unknownBytecode)
  
  		"2 byte bytecodes"
  		(2 224 224 extABytecode extension)
  		(2 225 225 extBBytecode extension)
  
  		"pushes"
  		(2 226 226 genExtPushReceiverVariableBytecode)		"Needs a frame for context inst var access"
  		(2 227 227 genExtPushLitVarDirSupBytecode			needsFrameNever: 1)
  		(2 228 228 genExtPushLiteralBytecode					needsFrameNever: 1)
  		(2 229 229 genLongPushTemporaryVariableBytecode)
  		(2 230 230 genPushClosureTempsBytecode)
  		(2 231 231 genPushNewArrayBytecode)
  		(2 232 232 genExtPushIntegerBytecode				needsFrameNever: 1)
  		(2 233 233 genExtPushCharacterBytecode				needsFrameNever: 1)
  
  		"returns"
  		"sends"
  		(2 234 234 genExtSendBytecode isMapped)
  		(2 235 235 genExtSendSuperBytecode isMapped)
  
  		"sista bytecodes"
+ 		(2 236 236 unknownBytecode)
- 		(2 236 236 genExtTrapIfNotInstanceOfBehaviorsBytecode isMapped)
  
  		"jumps"
  		(2 237 237 genExtUnconditionalJump	branch isMapped "because of interrupt check" v4:Long:Branch:Distance:)
  		(2 238 238 genExtJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  		(2 239 239 genExtJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  
  		"stores"
  		(2 240 240 genExtStoreAndPopReceiverVariableBytecode)
  		(2 241 241 genExtStoreAndPopLiteralVariableBytecode)
  		(2 242 242 genLongStoreAndPopTemporaryVariableBytecode)
  		(2 243 243 genExtStoreReceiverVariableBytecode)
  		(2 244 244 genExtStoreLiteralVariableBytecode)
  		(2 245 245 genLongStoreTemporaryVariableBytecode)
  
  		(2 246 247	unknownBytecode)
  
  		"3 byte bytecodes"
  		(3 248 248 genCallPrimitiveBytecode)
  		(3 249 249 unknownBytecode) "reserved for Push Float"
  		(3 250 250 genExtPushClosureBytecode block v4:Block:Code:Size:)
  		(3 251 251 genPushRemoteTempLongBytecode)
  		(3 252 252 genStoreRemoteTempLongBytecode)
  		(3 253 253 genStoreAndPopRemoteTempLongBytecode)
  
+ 		(3 254 254	genExtJumpIfNotInstanceOfBehaviorsOrPopBytecode)
+ 		
+ 		(3 255 255	unknownBytecode))!
- 		(3 254 255	unknownBytecode))!



More information about the Vm-dev mailing list