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

commits at source.squeak.org commits at source.squeak.org
Tue Apr 19 01:27:44 UTC 2016


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

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

Name: VMMaker.oscog-cb.1817
Author: cb
Time: 18 April 2016, 6:26:01.068449 pm
UUID: 3306d184-513f-4ee4-a56e-dfad6680f5ac
Ancestors: VMMaker.oscog-eem.1816

Removed all the annoteUse (from the struct, its usage, etc...)

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

Item was changed:
  ----- Method: CogRegisterAllocatingSimStackEntry>>ensureSpilledAt:from: (in category 'compile abstract instructions') -----
  ensureSpilledAt: baseOffset from: baseRegister
  	| inst |
  	<var: #inst type: #'AbstractInstruction *'>
  	spilled ifTrue:
  		[type = SSSpill ifTrue:
  			[self assert: (offset = baseOffset and: [register = baseRegister]).
  			 ^self]].
  	self assert: type ~= SSSpill.
  	cogit traceSpill: self.
  	type = SSConstant
  		ifTrue:
  			[inst := cogit genPushConstant: constant]
  		ifFalse:
  			[type = SSBaseOffset
  				ifTrue:
  					[ liveRegister = NoReg
  						ifTrue: 
  							[cogit MoveMw: offset r: register R: TempReg.
  					 		 inst := cogit PushR: TempReg ]
  						ifFalse: [ inst := cogit PushR: liveRegister]]
  				ifFalse:
  					[self assert: type = SSRegister.
  					 inst := cogit PushR: register].
  			 type := SSSpill.
  			 offset := baseOffset.
  			 register := baseRegister].
+ 	spilled := true.!
- 	spilled := true.
- 	self maybeAnnotateUse: inst!

Item was changed:
  ----- Method: CogRegisterAllocatingSimStackEntry>>popToReg: (in category 'compile abstract instructions') -----
  popToReg: reg
  	| inst |
  	<var: #inst type: #'AbstractInstruction *'>
  	liveRegister ~= NoReg
  		ifTrue: 
  			[inst := reg ~= liveRegister
  				ifTrue: [cogit MoveR: liveRegister R: reg]
  				ifFalse: [cogit Label] ]
  		ifFalse: 
  			[spilled
  				ifTrue:
  					[inst := cogit PopR: reg]
  				ifFalse:
  					[type caseOf: {
  						[SSBaseOffset]	-> [inst := cogit MoveMw: offset r: register R: reg].
  						[SSConstant]	-> [inst := cogit genMoveConstant: constant R: reg].
  						[SSRegister]	-> [inst := reg ~= register
  														ifTrue: [cogit MoveR: register R: reg]
  														ifFalse: [cogit Label]] }]].
- 	self maybeAnnotateUse: inst.
  	reg ~= TempReg ifTrue: [ liveRegister := reg ]!

Item was changed:
  ----- Method: CogRegisterAllocatingSimStackEntry>>printStateOn: (in category 'printing') -----
  printStateOn: aStream
  	<doNotGenerate> "Smalltalk-side only"
  	type isInteger ifFalse: [^self].
  	aStream nextPut: $(.
  	type caseOf: {
  		[SSBaseOffset]	-> [aStream
  								nextPutAll: 'bo ';
  								nextPutAll: (cogit backEnd nameForRegister: register).
  							offset negative ifFalse: [aStream nextPut: $+].
  							aStream print: offset].
  		[SSConstant]	-> [aStream
  								nextPutAll: 'const ';
  								print: constant].
  		[SSRegister]	-> [aStream
  								nextPutAll: 'reg ';
  								nextPutAll: (cogit backEnd nameForRegister: register)].
  		[SSSpill]		-> [aStream
  								nextPutAll: 'spill @ ';
  								nextPutAll: (cogit backEnd nameForRegister: register).
  							offset negative ifFalse: [aStream nextPut: $+].
  							aStream print: offset] }.
  	(spilled and: [type ~= SSSpill]) ifTrue:
  		[aStream nextPutAll: ' (spilled)'].
  	liveRegister ~= NoReg ifTrue:
  		[aStream nextPutAll: ' (live: '; nextPutAll: (cogit backEnd nameForRegister: liveRegister); nextPut: $)].
- 	annotateUse ifTrue:
- 		[aStream nextPutAll: ' (ANNOTATED)'].
  	bcptr ifNotNil:
  		[aStream space; nextPut: ${; print: bcptr; nextPut: $}].
  	aStream nextPut: $)!

Item was changed:
  ----- Method: CogRegisterAllocatingSimStackEntry>>storeToReg: (in category 'compile abstract instructions') -----
  storeToReg: reg
  	| inst |
  	<var: #inst type: #'AbstractInstruction *'>
  	liveRegister ~= NoReg
  		ifTrue:
  			[inst := reg ~= liveRegister
  							ifTrue: [cogit MoveR: liveRegister R: reg]
  							ifFalse: [cogit Label]]
  		ifFalse:
  			[type caseOf: {
  				[SSBaseOffset]	-> [inst := cogit MoveMw: offset r: register R: reg].
  				[SSSpill]		-> [inst := cogit MoveMw: offset r: register R: reg].
  				[SSConstant]	-> [inst := cogit genMoveConstant: constant R: reg].
  				[SSRegister]	-> [inst := reg ~= register
  												ifTrue: [cogit MoveR: register R: reg]
  												ifFalse: [cogit Label]] }].
- 	self maybeAnnotateUse: inst.
  	reg ~= TempReg ifTrue: [ liveRegister := reg ]!

Item was changed:
  ----- Method: CogSimStackEntry class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
  instVarNamesAndTypesForTranslationDo: aBinaryBlock
  	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a CogSimStackEntry struct."
  	"self printTypedefOn: Transcript"
  	self filteredInstVarNames do:
  		[:ivn|
  		aBinaryBlock
  			value: (ivn = 'register' ifTrue: ['registerr'] ifFalse: [ivn]) "avoid reservedWord conflict"
  			value: (ivn caseOf: {
  						['type']			-> [#char].
+ 						['spilled']		-> [#char].}
- 						['spilled']		-> [#char].
- 						['annotateUse']	-> [#char]}
  					otherwise:
  						[#sqInt])]!

Item was removed:
- ----- Method: CogSimStackEntry>>annotateUse (in category 'accessing') -----
- annotateUse
- 	"Answer the value of annotateUse"
- 
- 	^ annotateUse!

Item was removed:
- ----- Method: CogSimStackEntry>>annotateUse: (in category 'accessing') -----
- annotateUse: anObject
- 	"Set the value of annotateUse"
- 
- 	^annotateUse := anObject!

Item was changed:
  ----- Method: CogSimStackEntry>>ensureSpilledAt:from: (in category 'compile abstract instructions') -----
  ensureSpilledAt: baseOffset from: baseRegister
  	| inst |
  	<var: #inst type: #'AbstractInstruction *'>
  	spilled ifTrue:
  		[type = SSSpill ifTrue:
  			[self assert: (offset = baseOffset and: [register = baseRegister]).
  			 ^self]].
  	self assert: type ~= SSSpill.
  	cogit traceSpill: self.
  	type = SSConstant
  		ifTrue:
  			[inst := cogit genPushConstant: constant]
  		ifFalse:
  			[type = SSBaseOffset
  				ifTrue:
  					[cogit MoveMw: offset r: register R: TempReg.
  					 inst := cogit PushR: TempReg]
  				ifFalse:
  					[self assert: type = SSRegister.
  					 inst := cogit PushR: register].
  			 type := SSSpill.
  			 offset := baseOffset.
  			 register := baseRegister].
+ 	spilled := true.!
- 	spilled := true.
- 	self maybeAnnotateUse: inst!

Item was removed:
- ----- Method: CogSimStackEntry>>maybeAnnotateUse: (in category 'compile abstract instructions') -----
- maybeAnnotateUse: inst
- 	<inline: true>
- 	annotateUse ifTrue:
- 		[inst annotation = 0
- 			ifTrue: [cogit annotateBytecode: inst]
- 			ifFalse: [cogit annotateBytecode: cogit Label].
- 		 annotateUse := false]!

Item was changed:
  ----- Method: CogSimStackEntry>>popToReg: (in category 'compile abstract instructions') -----
  popToReg: reg
  	| inst |
  	<var: #inst type: #'AbstractInstruction *'>
  	spilled
  		ifTrue:
  			[inst := cogit PopR: reg]
  		ifFalse:
  			[type caseOf: {
  				[SSBaseOffset]	-> [inst := cogit MoveMw: offset r: register R: reg].
  				[SSConstant]	-> [inst := cogit genMoveConstant: constant R: reg].
  				[SSRegister]	-> [inst := reg ~= register
  												ifTrue: [cogit MoveR: register R: reg]
+ 												ifFalse: [cogit Label]] }].!
- 												ifFalse: [cogit Label]] }].
- 	self maybeAnnotateUse: inst!

Item was changed:
  ----- Method: CogSimStackEntry>>printStateOn: (in category 'printing') -----
  printStateOn: aStream
  	<doNotGenerate> "Smalltalk-side only"
  	type isInteger ifFalse: [^self].
  	aStream nextPut: $(.
  	type caseOf: {
  		[SSBaseOffset]	-> [aStream
  								nextPutAll: 'bo ';
  								nextPutAll: (cogit backEnd nameForRegister: register).
  							offset negative ifFalse: [aStream nextPut: $+].
  							aStream print: offset].
  		[SSConstant]	-> [aStream
  								nextPutAll: 'const ';
  								print: constant].
  		[SSRegister]	-> [aStream
  								nextPutAll: 'reg ';
  								nextPutAll: (cogit backEnd nameForRegister: register)].
  		[SSSpill]		-> [aStream
  								nextPutAll: 'spill @ ';
  								nextPutAll: (cogit backEnd nameForRegister: register).
  							offset negative ifFalse: [aStream nextPut: $+].
  							aStream print: offset] }.
  	(spilled and: [type ~= SSSpill]) ifTrue:
  		[aStream nextPutAll: ' (spilled)'].
- 	annotateUse ifTrue:
- 		[aStream nextPutAll: ' (ANNOTATED)'].
  	bcptr ifNotNil:
  		[aStream space; nextPut: ${; print: bcptr; nextPut: $}].
  	aStream nextPut: $)!

Item was changed:
  ----- Method: CogSimStackEntry>>storeToReg: (in category 'compile abstract instructions') -----
  storeToReg: reg
  	| inst |
  	<var: #inst type: #'AbstractInstruction *'>
  	type caseOf: {
  		[SSBaseOffset]	-> [inst := cogit MoveMw: offset r: register R: reg].
  		[SSSpill]		-> [inst := cogit MoveMw: offset r: register R: reg].
  		[SSConstant]	-> [inst := cogit genMoveConstant: constant R: reg].
  		[SSRegister]	-> [inst := reg ~= register
  										ifTrue: [cogit MoveR: register R: reg]
+ 										ifFalse: [cogit Label]] }!
- 										ifFalse: [cogit Label]] }.
- 	self maybeAnnotateUse: inst!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>ssStorePop:toPreferredReg: (in category 'simulation stack') -----
  ssStorePop: popBoolean toPreferredReg: preferredReg
  	"Store or pop the top simulated stack entry to a register.
  	 Use preferredReg if the entry is not itself a register.
  	 Answer the actual register the result ends up in."
  	| actualReg |
  	actualReg := preferredReg.
  	self ssTop type = SSRegister ifTrue: 
  		[self assert: self ssTop liveRegister = self ssTop register.
- 		self assert: self ssTop annotateUse not.
  		self assert: self ssTop spilled not].
  	self ssTop liveRegister ~= NoReg ifTrue:
  		[actualReg := self ssTop liveRegister].
  	self ssStorePop: popBoolean toReg: actualReg. "generates nothing if ssTop is already in actualReg"
  	^ actualReg!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genSpecialSelectorComparison (in category 'bytecode generators') -----
  genSpecialSelectorComparison
  	"Override to count inlined branches if followed by a conditional branch.
  	 We borrow the following conditional branch's counter and when about to
  	 inline the comparison we decrement the counter (without writing it back)
  	 and if it trips simply abort the inlining, falling back to the normal send which
  	 will then continue to the conditional branch which will trip and enter the abort."
  	| nextPC postBranchPC targetBytecodePC primDescriptor branchDescriptor
+ 	  rcvrIsInt argIsInt argInt jumpNotSmallInts inlineCAB
- 	  rcvrIsInt argIsInt argInt jumpNotSmallInts inlineCAB annotateInst
  	  counterAddress countTripped counterReg index |
  	<var: #countTripped type: #'AbstractInstruction *'>
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpNotSmallInts type: #'AbstractInstruction *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  
  	(coInterpreter isOptimizedMethod: methodObj) ifTrue: [ ^ self genSpecialSelectorComparisonWithoutCounters ].
  
  	self ssFlushTo: simStackPtr - 2.
  	primDescriptor := self generatorAt: byte0.
  	argIsInt := self ssTop type = SSConstant
  				 and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
  	rcvrIsInt := (self ssValue: 1) type = SSConstant
  				 and: [objectMemory isIntegerObject: (self ssValue: 1) constant].
  
  	"short-cut the jump if operands are SmallInteger constants."
  	(argIsInt and: [rcvrIsInt]) ifTrue:
  		[^ self genStaticallyResolvedSpecialSelectorComparison].
  
  	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
  		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
  	
  	"Only interested in inlining if followed by a conditional branch."
  	inlineCAB := branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse].
  	"Further, only interested in inlining = and ~= if there's a SmallInteger constant involved.
  	 The relational operators successfully statically predict SmallIntegers; the equality operators do not."
  	(inlineCAB and: [primDescriptor opcode = JumpZero or: [primDescriptor opcode = JumpNonZero]]) ifTrue:
  		[inlineCAB := argIsInt or: [rcvrIsInt]].
  	inlineCAB ifFalse:
  		[^self genSpecialSelectorSend].
  
  	argIsInt
  		ifTrue:
  			[(self ssValue: 1) popToReg: ReceiverResultReg.
- 			 annotateInst := self ssTop annotateUse.
  			 self ssPop: 2.
  			 self MoveR: ReceiverResultReg R: TempReg]
  		ifFalse:
  			[self marshallSendArguments: 1.
  			 self MoveR: Arg0Reg R: TempReg].
  	jumpNotSmallInts := (argIsInt or: [rcvrIsInt])
  							ifTrue: [objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg]
  							ifFalse: [objectRepresentation genJumpNotSmallIntegersIn: ReceiverResultReg andScratch: TempReg scratch: ClassReg].
  
  	counterReg := self allocateRegNotConflictingWith: (self registerMaskFor: ReceiverResultReg and: Arg0Reg).
  	self 
  		genExecutionCountLogicInto: [ :cAddress :countTripBranch | 
  			counterAddress := cAddress. 
  			countTripped := countTripBranch ] 
  		counterReg: counterReg.
  
  	argIsInt
+ 		ifTrue: [self CmpCq: argInt R: ReceiverResultReg]
- 		ifTrue: [annotateInst
- 					ifTrue: [self annotateBytecode: (self CmpCq: argInt R: ReceiverResultReg)]
- 					ifFalse: [self CmpCq: argInt R: ReceiverResultReg]]
  		ifFalse: [self CmpR: Arg0Reg R: ReceiverResultReg].
  	"Cmp is weird/backwards so invert the comparison.  Further since there is a following conditional
  	 jump bytecode define non-merge fixups and leave the cond bytecode to set the mergeness."
  	self genConditionalBranch: (branchDescriptor isBranchTrue
  				ifTrue: [primDescriptor opcode]
  				ifFalse: [self inverseBranchFor: primDescriptor opcode])
  		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  		
  	self genFallsThroughCountLogicCounterReg: counterReg counterAddress: counterAddress.
  	
  	self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
  	countTripped jmpTarget: (jumpNotSmallInts jmpTarget: self Label).
  	
  	argIsInt ifTrue:
  		[self MoveCq: argInt R: Arg0Reg].
  	index := byte0 - self firstSpecialSelectorBytecodeOffset.
  	^self genMarshalledSend: index negated - 1 numArgs: 1 sendTable: ordinarySendTrampolines!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>annotateBytecodeIfAnnotated: (in category 'bytecode generator support') -----
- annotateBytecodeIfAnnotated: aSimStackEntry
- 	<var: #aSimStackEntry type: #'CogSimStackEntry *'>
- 	<inline: false>
- 	aSimStackEntry annotateUse ifTrue:
- 		[self annotateBytecode: (self prevInstIsPCAnnotated
- 									ifTrue: [self Nop]
- 									ifFalse: [self Label]).
- 		 aSimStackEntry annotateUse: false]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>doubleExtendedDoAnythingBytecode (in category 'bytecode generators') -----
  doubleExtendedDoAnythingBytecode
  	"Replaces the Blue Book double-extended send [132], in which the first byte was wasted on 8 bits of argument count. 
  	Here we use 3 bits for the operation sub-type (opType),  and the remaining 5 bits for argument count where needed. 
  	The last byte give access to 256 instVars or literals. 
  	See also secondExtendedSendBytecode"
  	| opType |
  	opType := byte1 >> 5.
  	opType = 0 ifTrue:
  		[^self genSend: byte2 numArgs: (byte1 bitAnd: 31)].
  	opType = 1 ifTrue:
  		[^self genSendSuper: byte2 numArgs: (byte1 bitAnd: 31)].
  	"We need a map entry for this bytecode for correct parsing.
  	 The sends will get an IsSend entry anyway.  The other cases need a fake one."
  	opType caseOf: {
  			[2]	->	[(coInterpreter isReadMediatedContextInstVarIndex: byte2)
  						ifTrue: [self genPushMaybeContextReceiverVariable: byte2]
  						ifFalse: [self genPushReceiverVariable: byte2.
+ 								self annotateBytecode: self Label.
- 								self ssTop annotateUse: true.
  								^0]].
  			[3]	->	[self genPushLiteralIndex: byte2.
+ 					 self annotateBytecode: self Label.
- 					 self ssTop annotateUse: true.
  					 ^0].
  			[4]	->	[self genPushLiteralVariable: byte2.].
  			[7]	->	[self genStorePop: false LiteralVariable: byte2.
  					self cppIf: IMMUTABILITY ifTrue: [ "genStorePop:LiteralVariable: annotates; don't annotate twice" ^0 ] ] }
  		otherwise: "5 & 6"
  			[(coInterpreter isWriteMediatedContextInstVarIndex: byte2)
  				ifTrue: [self genStorePop: opType = 6 MaybeContextReceiverVariable: byte2]
  				ifFalse: [self genStorePop: opType = 6 ReceiverVariable: byte2].
  			self cppIf: IMMUTABILITY ifTrue: [ "genStorePop:LiteralVariable: annotates; don't annotate twice" ^0 ]].
  	"We need a map entry for this bytecode for correct parsing (if the method builds a frame)."
  	self assert: needsFrame.
  	"genPushMaybeContextInstVar, pushListVar, store & storePop all generate code"
  	self assert: self prevInstIsPCAnnotated not.
  	self annotateBytecode: self Label.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genJumpIf:to: (in category 'bytecode generator support') -----
  genJumpIf: boolean to: targetBytecodePC
  	<inline: false>
  	| desc fixup ok |
  	<var: #desc type: #'CogSimStackEntry *'>
  	<var: #fixup type: #'BytecodeFixup *'>
  	<var: #ok type: #'AbstractInstruction *'>
  	self ssFlushTo: simStackPtr - 1.
  	desc := self ssTop.
  	self ssPop: 1.
  	(desc type == SSConstant
  	 and: [desc constant = objectMemory trueObject or: [desc constant = objectMemory falseObject]]) ifTrue:
  		["Must arrange there's a fixup at the target whether it is jumped to or
  		  not so that the simStackPtr can be kept correct."
  		 fixup := self ensureFixupAt: targetBytecodePC - initialPC.
- 		 "Must enter any annotatedConstants into the map"
- 		 desc annotateUse ifTrue:
- 			[self annotateBytecode: (self prevInstIsPCAnnotated
- 											ifTrue: [self Nop]
- 											ifFalse: [self Label])].
  		 "Must annotate the bytecode for correct pc mapping."
  		 self annotateBytecode: (desc constant = boolean
  									ifTrue: [self Jump: fixup]
  									ifFalse: [self prevInstIsPCAnnotated
  												ifTrue: [self Nop]
  												ifFalse: [self Label]]).
  		 ^0].
  	desc popToReg: TempReg.
  	"Cunning trick by LPD.  If true and false are contiguous subtract the smaller.
  	 Correct result is either 0 or the distance between them.  If result is not 0 or
  	 their distance send mustBeBoolean."
  	self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.
  	self genSubConstant: boolean R: TempReg.
  	self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).
  	
  	self extASpecifiesNoMustBeBoolean ifTrue: 
  		[ extA := 0. 
  		self annotateBytecode: self lastOpcode.
  		^ 0].
  	extA := 0.
  	
  .	self CmpCq: (boolean == objectMemory falseObject
  					ifTrue: [objectMemory trueObject - objectMemory falseObject]
  					ifFalse: [objectMemory falseObject - objectMemory trueObject])
  		R: TempReg.
  	ok := self JumpZero: 0.
  	self CallRT: (boolean == objectMemory falseObject
  					ifTrue: [ceSendMustBeBooleanAddFalseTrampoline]
  					ifFalse: [ceSendMustBeBooleanAddTrueTrampoline]).
  	ok jmpTarget: (self annotateBytecode: self Label).
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPopStackBytecode (in category 'bytecode generators') -----
  genPopStackBytecode
- 	self annotateBytecodeIfAnnotated: self ssTop.
  	self ssTop spilled ifTrue:
  		[self AddCq: objectMemory wordSize R: SPReg].
  	self ssPop: 1.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSpecialSelectorArithmetic (in category 'bytecode generators') -----
  genSpecialSelectorArithmetic
  	| primDescriptor rcvrIsConst argIsConst rcvrIsInt argIsInt rcvrInt argInt result
+ 	 jumpNotSmallInts jumpContinue index |
- 	 jumpNotSmallInts jumpContinue annotateInst instToAnnotate index |
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpNotSmallInts type: #'AbstractInstruction *'>
  	<var: #jumpContinue type: #'AbstractInstruction *'>
  	<var: #instToAnnotate type: #'AbstractInstruction *'>
  	primDescriptor := self generatorAt: byte0.
  	argIsInt := (argIsConst := self ssTop type = SSConstant)
  				 and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
  	rcvrIsInt := (rcvrIsConst := (self ssValue: 1) type = SSConstant)
  				 and: [objectMemory isIntegerObject: (rcvrInt := (self ssValue: 1) constant)].
  
  	(argIsInt and: [rcvrIsInt]) ifTrue:
  		[rcvrInt := objectMemory integerValueOf: rcvrInt.
  		 argInt := objectMemory integerValueOf: argInt.
  		 primDescriptor opcode caseOf: {
  			[AddRR]	-> [result := rcvrInt + argInt].
  			[SubRR]	-> [result := rcvrInt - argInt].
  			[AndRR]	-> [result := rcvrInt bitAnd: argInt].
  			[OrRR]	-> [result := rcvrInt bitOr: argInt] }.
  		(objectMemory isIntegerValue: result) ifTrue:
+ 			["Must annotate the bytecode for correct pc mapping."
- 			["Must enter any annotatedConstants into the map"
- 			 self annotateBytecodeIfAnnotated: (self ssValue: 1).
- 			 self annotateBytecodeIfAnnotated: self ssTop.
- 			 "Must annotate the bytecode for correct pc mapping."
  			^self ssPop: 2; ssPushAnnotatedConstant: (objectMemory integerObjectOf: result)].
  		^self genSpecialSelectorSend].
  
  	"If there's any constant involved other than a SmallInteger don't attempt to inline."
  	((rcvrIsConst and: [rcvrIsInt not])
  	 or: [argIsConst and: [argIsInt not]]) ifTrue:
  		[^self genSpecialSelectorSend].
  
  	"If we know nothing about the types then better not to inline as the inline cache and
  	 primitive code is not terribly slow so wasting time on duplicating tag tests is pointless."
  	(argIsInt or: [rcvrIsInt]) ifFalse:
  		[^self genSpecialSelectorSend].
  
  	argIsInt
  		ifTrue:
  			[self ssFlushTo: simStackPtr - 2.
  			 (self ssValue: 1) popToReg: ReceiverResultReg.
- 			 annotateInst := self ssTop annotateUse.
  			 self ssPop: 2.
  			 self MoveR: ReceiverResultReg R: TempReg]
  		ifFalse:
  			[self marshallSendArguments: 1.
  			 self MoveR: Arg0Reg R: TempReg].
  	jumpNotSmallInts := (argIsInt or: [rcvrIsInt])
  							ifTrue: [objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg]
  							ifFalse: [objectRepresentation genJumpNotSmallIntegersIn: ReceiverResultReg andScratch: TempReg scratch: ClassReg].
  	primDescriptor opcode caseOf: {
  		[AddRR] -> [argIsInt
  						ifTrue:
+ 							[self AddCq: argInt - ConstZero R: ReceiverResultReg.
- 							[instToAnnotate := self AddCq: argInt - ConstZero R: ReceiverResultReg.
  							 jumpContinue := self JumpNoOverflow: 0.
  							 "overflow; must undo the damage before continuing"
  							 self SubCq: argInt - ConstZero R: ReceiverResultReg]
  						ifFalse:
  							[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: ReceiverResultReg.
  							 self AddR: Arg0Reg R: ReceiverResultReg.
  							jumpContinue := self JumpNoOverflow: 0.
  							"overflow; must undo the damage before continuing"
  							 rcvrIsInt
  								ifTrue: [self MoveCq: rcvrInt R: ReceiverResultReg]
  								ifFalse:
  									[self SubR: Arg0Reg R: ReceiverResultReg.
  									 objectRepresentation genSetSmallIntegerTagsIn: ReceiverResultReg]]].
  		[SubRR] -> [argIsInt
  						ifTrue:
+ 							[self SubCq: argInt - ConstZero R: ReceiverResultReg.
- 							[instToAnnotate := self SubCq: argInt - ConstZero R: ReceiverResultReg.
  							 jumpContinue := self JumpNoOverflow: 0.
  							 "overflow; must undo the damage before continuing"
  							 self AddCq: argInt - ConstZero R: ReceiverResultReg]
  						ifFalse:
  							[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: Arg0Reg.
  							 self SubR: Arg0Reg R: ReceiverResultReg.
  							 jumpContinue := self JumpNoOverflow: 0.
  							 "overflow; must undo the damage before continuing"
  							 self AddR: Arg0Reg R: ReceiverResultReg.
  							 objectRepresentation genSetSmallIntegerTagsIn: Arg0Reg]].
  		[AndRR] -> [argIsInt
+ 						ifTrue: [self AndCq: argInt R: ReceiverResultReg]
- 						ifTrue: [instToAnnotate := self AndCq: argInt R: ReceiverResultReg]
  						ifFalse: [self AndR: Arg0Reg R: ReceiverResultReg].
  					jumpContinue := self Jump: 0].
  		[OrRR]	-> [argIsInt
+ 						ifTrue: [self OrCq: argInt R: ReceiverResultReg]
- 						ifTrue: [instToAnnotate := self OrCq: argInt R: ReceiverResultReg]
  						ifFalse: [self OrR: Arg0Reg R: ReceiverResultReg].
  					jumpContinue := self Jump: 0] }.
  	jumpNotSmallInts jmpTarget: self Label.
  	argIsInt ifTrue:
+ 		[self MoveCq: argInt R: Arg0Reg].
- 		[annotateInst ifTrue: [self annotateBytecode: instToAnnotate].
- 		 self MoveCq: argInt R: Arg0Reg].
  	index := byte0 - self firstSpecialSelectorBytecodeOffset.
  	self genMarshalledSend: index negated - 1 numArgs: 1 sendTable: ordinarySendTrampolines.
  	jumpContinue jmpTarget: self Label.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSpecialSelectorComparison (in category 'bytecode generators') -----
  genSpecialSelectorComparison
  	| nextPC postBranchPC targetBytecodePC primDescriptor branchDescriptor
+ 	  rcvrIsInt argIsInt argInt jumpNotSmallInts inlineCAB index |
- 	  rcvrIsInt argIsInt argInt jumpNotSmallInts inlineCAB annotateInst index |
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpNotSmallInts type: #'AbstractInstruction *'>
  	self ssFlushTo: simStackPtr - 2.
  	primDescriptor := self generatorAt: byte0.
  	argIsInt := self ssTop type = SSConstant
  				 and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
  	rcvrIsInt := (self ssValue: 1) type = SSConstant
  				 and: [objectMemory isIntegerObject: (self ssValue: 1) constant].
  
  	(argIsInt and: [rcvrIsInt]) ifTrue:
  		[^ self genStaticallyResolvedSpecialSelectorComparison].
  
  	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
  		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
  
  	"Only interested in inlining if followed by a conditional branch."
  	inlineCAB := branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse].
  	"Further, only interested in inlining = and ~= if there's a SmallInteger constant involved.
  	 The relational operators successfully statically predict SmallIntegers; the equality operators do not."
  	(inlineCAB and: [primDescriptor opcode = JumpZero or: [primDescriptor opcode = JumpNonZero]]) ifTrue:
  		[inlineCAB := argIsInt or: [rcvrIsInt]].
  	inlineCAB ifFalse:
  		[^self genSpecialSelectorSend].
  
  	argIsInt
  		ifTrue:
  			[(self ssValue: 1) popToReg: ReceiverResultReg.
- 			 annotateInst := self ssTop annotateUse.
  			 self ssPop: 2.
  			 self MoveR: ReceiverResultReg R: TempReg]
  		ifFalse:
  			[self marshallSendArguments: 1.
  			 self MoveR: Arg0Reg R: TempReg].
  	jumpNotSmallInts := (argIsInt or: [rcvrIsInt])
  							ifTrue: [objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg]
  							ifFalse: [objectRepresentation genJumpNotSmallIntegersIn: ReceiverResultReg andScratch: TempReg scratch: ClassReg].
  	argIsInt
+ 		ifTrue: [self CmpCq: argInt R: ReceiverResultReg]
- 		ifTrue: [annotateInst
- 					ifTrue: [self annotateBytecode: (self CmpCq: argInt R: ReceiverResultReg)]
- 					ifFalse: [self CmpCq: argInt R: ReceiverResultReg]]
  		ifFalse: [self CmpR: Arg0Reg R: ReceiverResultReg].
  	"Cmp is weird/backwards so invert the comparison.  Further since there is a following conditional
  	 jump bytecode define non-merge fixups and leave the cond bytecode to set the mergeness."
  	self genConditionalBranch: (branchDescriptor isBranchTrue
  				ifTrue: [primDescriptor opcode]
  				ifFalse: [self inverseBranchFor: primDescriptor opcode])
  		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  	self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
  	jumpNotSmallInts jmpTarget: self Label.
  	argIsInt ifTrue:
  		[self MoveCq: argInt R: Arg0Reg].
  	index := byte0 - self firstSpecialSelectorBytecodeOffset.
  	^self genMarshalledSend: index negated - 1 numArgs: 1 sendTable: ordinarySendTrampolines!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genStaticallyResolvedSpecialSelectorComparison (in category 'bytecode generator support') -----
  genStaticallyResolvedSpecialSelectorComparison
  	"Assumes both operands are ints"
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	| rcvrInt argInt primDescriptor result |
  	primDescriptor := self generatorAt: byte0.
  	argInt := self ssTop constant.
  	rcvrInt := (self ssValue: 1) constant.
  	self cCode: '' inSmalltalk: "In Simulator ints are unsigned..."
  		[rcvrInt := objectMemory integerValueOf: rcvrInt.
  		argInt := objectMemory integerValueOf: argInt].
  	 primDescriptor opcode caseOf: {
  		[JumpLess]				-> [result := rcvrInt < argInt].
  		[JumpLessOrEqual]		-> [result := rcvrInt <= argInt].
  		[JumpGreater]			-> [result := rcvrInt > argInt].
  		[JumpGreaterOrEqual]	-> [result := rcvrInt >= argInt].
  		[JumpZero]				-> [result := rcvrInt = argInt].
  		[JumpNonZero]			-> [result := rcvrInt ~= argInt] }.
- 	 "Must enter any annotatedConstants into the map"
- 	 self annotateBytecodeIfAnnotated: (self ssValue: 1).
- 	 self annotateBytecodeIfAnnotated: self ssTop.
  	 "Must annotate the bytecode for correct pc mapping."
  	 self ssPop: 2.
  	 ^self ssPushAnnotatedConstant: (result
  			ifTrue: [objectMemory trueObject]
  			ifFalse: [objectMemory falseObject])!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>initSimStackForFramefulMethod: (in category 'simulation stack') -----
  initSimStackForFramefulMethod: startpc
  	<var: #desc type: #'CogSimStackEntry *'>
  	simSelf
  		type: SSBaseOffset;
  		spilled: true;
- 		annotateUse: false;
  		register: FPReg;
  		offset: FoxMFReceiver.
  	optStatus 
  		isReceiverResultRegLive: false;
  		ssEntry: (self addressOf: simSelf).
  	simSpillBase := methodOrBlockNumTemps. "N.B. Includes num args"
  	simStackPtr := simSpillBase - 1.
  	"args"
  	0 to: methodOrBlockNumArgs - 1 do:
  		[:i| | desc |
  		desc := self simStackAt: i.
  		desc
  			type: SSBaseOffset;
  			spilled: true;
- 			annotateUse: false;
  			register: FPReg;
  			offset: FoxCallerSavedIP + ((methodOrBlockNumArgs - i) * objectMemory wordSize);
  			bcptr: startpc].
  	"temps"
  	methodOrBlockNumArgs to: simStackPtr do:
  		[:i| | desc |
  		desc := self simStackAt: i.
  		desc
  			type: SSBaseOffset;
  			spilled: true;
- 			annotateUse: false;
  			register: FPReg;
  			offset: FoxMFReceiver - (i - methodOrBlockNumArgs + 1 * objectMemory wordSize);
  			bcptr: startpc]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>initSimStackForFramelessBlock: (in category 'simulation stack') -----
  initSimStackForFramelessBlock: startpc
  	"The register receiver (the closure itself) and args are pushed by the closure value primitive(s)
  	 and hence a frameless block has all arguments and copied values pushed to the stack.  However,
  	 the method receiver (self) is put in the ReceiverResultRegister by the block entry."
  	| desc |
  	<var: #desc type: #'CogSimStackEntry *'>
  	simSelf
  		type: SSRegister;
  		spilled: false;
- 		annotateUse: false;
  		register: ReceiverResultReg.
  	optStatus
  		isReceiverResultRegLive: true;
  		ssEntry: (self addressOf: simSelf).
  	self assert: methodOrBlockNumTemps >= methodOrBlockNumArgs.
  	0 to: methodOrBlockNumTemps - 1 do:
  		[:i|
  		desc := self simStackAt: i.
  		desc
  			type: SSBaseOffset;
  			spilled: true;
- 			annotateUse: false;
  			register: SPReg;
  			offset: ((backEnd hasLinkRegister
  								ifTrue: [methodOrBlockNumArgs - 1- i]
  								ifFalse: [methodOrBlockNumArgs - i]) * objectMemory wordSize);
  			bcptr: startpc].
  	simSpillBase := simStackPtr := methodOrBlockNumTemps - 1!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>initSimStackForFramelessMethod: (in category 'simulation stack') -----
  initSimStackForFramelessMethod: startpc
  	| desc |
  	<var: #desc type: #'CogSimStackEntry *'>
  	simSelf
  		type: SSRegister;
  		spilled: false;
- 		annotateUse: false;
  		register: ReceiverResultReg.
  	optStatus
  		isReceiverResultRegLive: true;
  		ssEntry: (self addressOf: simSelf).
  	self assert: methodOrBlockNumTemps >= methodOrBlockNumArgs.
  	self assert: self numRegArgs <= 2.
  	(methodOrBlockNumArgs between: 1 and: self numRegArgs)
  		ifTrue:
  			[desc := self simStackAt: 0.
  			 desc
  				type: SSRegister;
  				spilled: false;
- 				annotateUse: false;
  				register: Arg0Reg;
  				bcptr: startpc.
  			 methodOrBlockNumArgs > 1 ifTrue:
  				[desc := self simStackAt: 1.
  				 desc
  					type: SSRegister;
  					spilled: false;
- 					annotateUse: false;
  					register: Arg1Reg;
  					bcptr: startpc]]
  		ifFalse:
  			[0 to: methodOrBlockNumArgs - 1 do:
  				[:i|
  				desc := self simStackAt: i.
  				desc
  					type: SSBaseOffset;
  					register: SPReg;
  					spilled: true;
- 					annotateUse: false;
  					offset: ((backEnd hasLinkRegister
  								ifTrue: [methodOrBlockNumArgs - 1- i]
  								ifFalse: [methodOrBlockNumArgs - i]) * objectMemory wordSize);
  					bcptr: startpc]].
  	simSpillBase := simStackPtr := methodOrBlockNumArgs - 1!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssPushAnnotatedConstant: (in category 'simulation stack') -----
  ssPushAnnotatedConstant: literal
  	self ssPush: 1.
  	self updateSimSpillBase.
  	self ssTop
  		type: SSConstant;
- 		annotateUse: true;
  		spilled: false;
  		constant: literal;
  		bcptr: bytecodePC.
+ 	self annotateBytecode: self Label.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssPushBase:offset: (in category 'simulation stack') -----
  ssPushBase: reg offset: offset
  	self ssPush: 1.
  	self updateSimSpillBase.
  	self ssTop
  		type: SSBaseOffset;
  		spilled: false;
- 		annotateUse: false;
  		register: reg;
  		offset: offset;
  		bcptr: bytecodePC.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssPushConstant: (in category 'simulation stack') -----
  ssPushConstant: literal
  	self ssPush: 1.
  	self updateSimSpillBase.
  	self ssTop
  		type: SSConstant;
  		spilled: false;
- 		annotateUse: false;
  		constant: literal;
  		bcptr: bytecodePC.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssPushDesc: (in category 'simulation stack') -----
  ssPushDesc: simStackEntry
  	<var: #simStackEntry type: #SimStackEntry>
  	self cCode:
  			[simStackEntry type = SSSpill ifTrue:
  				[simStackEntry type: SSBaseOffset].
  			simStackEntry
  				spilled: false;
- 				annotateUse: false;
  				bcptr: bytecodePC.
  			 simStack
  				at: (simStackPtr := simStackPtr + 1)
  				put: simStackEntry]
  		inSmalltalk:
  			[(simStack at: (simStackPtr := simStackPtr + 1))
  				copyFrom: simStackEntry;
  				type: (simStackEntry type = SSSpill
  						ifTrue: [SSBaseOffset]
  						ifFalse: [simStackEntry type]);
  				spilled: false;
- 				annotateUse: false;
  				bcptr: bytecodePC].
  	self updateSimSpillBase.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssPushRegister: (in category 'simulation stack') -----
  ssPushRegister: reg
  	self ssPush: 1.
  	self updateSimSpillBase.
  	self ssTop
  		type: SSRegister;
  		spilled: false;
- 		annotateUse: false;
  		register: reg;
  		bcptr: bytecodePC.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssStorePop:toPreferredReg: (in category 'simulation stack') -----
  ssStorePop: popBoolean toPreferredReg: preferredReg
  	"Store or pop the top simulated stack entry to a register.
  	 Use preferredReg if the entry is not itself a register.
  	 Answer the actual register the result ends up in."
  	| actualReg |
  	actualReg := preferredReg.
  	self ssTop type = SSRegister ifTrue: 
+ 		[self assert: self ssTop spilled not.
+ 		 actualReg := self ssTop register].
- 		[ self assert: self ssTop annotateUse not.
- 		self assert: self ssTop spilled not.
- 		actualReg := self ssTop register].
  	self ssStorePop: popBoolean toReg: actualReg. "generates nothing if ssTop is already in actualReg"
  	^ actualReg!



More information about the Vm-dev mailing list