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

commits at source.squeak.org commits at source.squeak.org
Wed Apr 12 00:53:03 UTC 2017


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

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

Name: VMMaker.oscog-eem.2190
Author: eem
Time: 11 April 2017, 5:52:10.631026 pm
UUID: 7752b22c-922c-4063-88f7-d8ee8a016cb6
Ancestors: VMMaker.oscog-eem.2189

Sista Cogit:
Implement ensureAllocatableSlots: support.

RegisterAllocatingCogit:
liveRegisters must work in frameless methods.
Fix yet another methodOrBlockNumArgs/Temps mixup (this time in an assert).
Add assertCorrectSimStackPtr and revert StackToRegisterMappingCogit's one; duplicateRegisterAssignmentsInTemporaries is a RegisterAllocatingCogit thang..

Misc: Eliminate some breaks left in various methods by mistake.

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

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genGetInstanceOf:into:initializingIf: (in category 'bytecode generator support') -----
  genGetInstanceOf: classObj into: destReg initializingIf: initializeInstance
  	"Create an instance of classObj and assign it to destReg, initializing the instance
  	 if initializeInstance is true with nil or 0 as appropriate This is for inline primitives.
  	 Assume there is sufficient space in new space to complete the operation.
  	 Answer zero on success."
  	| classIndex classFormat header slots |
  	((objectMemory isNonImmediate: classObj)
  	 and: [(coInterpreter objCouldBeClassObj: classObj)
  	 and: [(classIndex := objectMemory rawHashBitsOf: classObj) ~= 0
  	 and: [(objectMemory isFixedSizePointerFormat: (objectMemory instSpecOfClassFormat: (classFormat := objectMemory formatOfClass: classObj)))
  	 and: [(slots := objectMemory fixedFieldsOfClassFormat: classFormat) < objectMemory numSlotsMask]]]]) ifFalse:
  		[^UnimplementedOperation].
  
+ 	self deny: destReg = TempReg.
+ 
  	header := objectMemory
  					headerForSlots: slots
  					format: (objectMemory instSpecOfClassFormat: classFormat)
  					classIndex: classIndex.
  
  	cogit MoveAw: objectMemory freeStartAddress R: destReg.
  	self genStoreHeader: header intoNewInstance: destReg using: TempReg.
  	cogit
  		LoadEffectiveAddressMw: (objectMemory smallObjectBytesForSlots: slots) r: destReg R: TempReg;
  		MoveR: TempReg Aw: objectMemory freeStartAddress.
  	(initializeInstance and: [slots > 0]) ifTrue:
  		[cogit genMoveConstant: objectMemory nilObject R: TempReg.
  		 0 to: slots - 1 do:
  			[:i| cogit MoveR: TempReg
  					Mw: i * objectMemory wordSize + objectMemory baseHeaderSize
  					r: destReg]].
  	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genSetGCNeeded (in category 'bytecode generator support') -----
+ genSetGCNeeded
+ 	<inline: true>
+ 	cogit
+ 		MoveCq: 1 R: TempReg;
+ 		MoveR: TempReg Aw: coInterpreter needGCFlagAddress!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>needGCFlagAddress (in category 'accessing') -----
+ needGCFlagAddress
+ 	^self addressForLabel: #needGCFlag!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>scavengeThreshold (in category 'accessing') -----
+ scavengeThreshold
+ 	^objectMemory scavengeThreshold!

Item was changed:
  ----- Method: InterpreterPrimitives>>sHEAFn (in category 'simulation support') -----
  sHEAFn
  	<doNotGenerate>
- 	self break.
  	^true!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>assertCorrectSimStackPtr (in category 'compile abstract instructions') -----
+ assertCorrectSimStackPtr
+ 	<inline: true> "generates nothing anyway"
+ 	 self cCode: '' inSmalltalk:
+ 		[deadCode ifFalse:
+ 			[self assert: simStackPtr + (needsFrame ifTrue: [0] ifFalse: [1])
+ 						= (self debugStackPointerFor: bytecodePC)].
+ 		 self deny: self duplicateRegisterAssignmentsInTemporaries].
+ 	!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>liveRegisters (in category 'simulation stack') -----
  liveRegisters
  	| regsSet |
+ 	needsFrame
+ 		ifTrue: [regsSet := 0]
+ 		ifFalse:
+ 			[regsSet := (methodOrBlockNumArgs > self numRegArgs
+ 						  or: [methodOrBlockNumArgs = 0])
+ 							ifTrue:
+ 								[self registerMaskFor: ReceiverResultReg]
+ 							ifFalse:
+ 								[(self numRegArgs > 1 and: [methodOrBlockNumArgs > 1])
+ 									ifFalse: [self registerMaskFor: ReceiverResultReg and: Arg0Reg]
+ 									ifTrue: [self registerMaskFor: ReceiverResultReg and: Arg0Reg and: Arg1Reg]]].
- 	self assert: needsFrame.
- 	regsSet := 0.
  	0 to: simStackPtr do:
  		[:i|
  		regsSet := regsSet bitOr: (self simStackAt: i) registerMask].
  	LowcodeVM ifTrue:
  		[(simNativeSpillBase max: 0) to: simNativeStackPtr do:
  			[:i|
  			regsSet := regsSet bitOr: (self simNativeStackAt: i) nativeRegisterMask]].
  	^regsSet!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>mergeCurrentSimStackWith:forwards: (in category 'bytecode generator support') -----
  mergeCurrentSimStackWith: fixup forwards: forwards
  	"At a merge point the cogit expects the stack to be in the same state as mergeSimStack.
  	 mergeSimStack is the state as of some jump forward or backward to this point.  So make simStack agree
  	 with mergeSimStack (it is, um, problematic to plant code at the jump).
  	 Values may have to be assigned to registers.  Registers may have to be swapped.
  	 The state of optStatus must agree.
  	 Generate code to merge the current simStack with that of the target fixup,
  	 the goal being to keep as many registers live as possible.  If the merge is forwards
  	 registers can be deassigned (since registers are always written to temp vars).
  	 But if backwards, nothing can be deassigned, and the state /must/ reflect the target."
  	"self printSimStack; printSimStack: fixup mergeSimStack"
  	"abstractOpcodes object copyFrom: startIndex to: opcodeIndex"
  	<var: #fixup type: #'BytecodeFixup *'>
  	| startIndex mergeSimStack currentEntry targetEntry writtenToRegisters |
  	<var: #mergeSimStack type: #'SimStackEntry *'>
  	<var: #targetEntry type: #'SimStackEntry *'>
  	<var: #currentEntry type: #'SimStackEntry *'>
  	(mergeSimStack := fixup mergeSimStack) ifNil: [^self].
  	startIndex := opcodeIndex. "for debugging"
  	"Assignments amongst the registers must be made in order to avoid overwriting.
  	 If necessary exchange registers amongst simStack's entries to resolve any conflicts."
  	self resolveRegisterOrderConflictsBetweenCurrentSimStackAnd: mergeSimStack.
  	(self asserta: (self conflictsResolvedBetweenSimStackAnd: mergeSimStack)) ifFalse:
  		[Notification new tag: #failedMerge; signal].
  	"Compute written to registers.  Perhaps we should use 0 in place of methodOrBlockNumTemps
  	 but Smalltalk does not assign to arguments."
  	writtenToRegisters := 0.
  	(self pushForMergeWith: mergeSimStack)
  		ifTrue:
  			[methodOrBlockNumTemps to: simStackPtr do:
  				[:i|
  				 currentEntry := self simStack: simStack at: i.
  				 targetEntry := self simStack: mergeSimStack at: i.
  				 writtenToRegisters := writtenToRegisters bitOr: targetEntry registerMask.
  				 (currentEntry reconcileForwardsWith: targetEntry) ifTrue:
  					[self assert: i >= methodOrBlockNumTemps.
  					 self deassignRegisterForTempVar: targetEntry in: mergeSimStack.
  					 targetEntry
  						type: SSRegister;
  						register: targetEntry liveRegister].
  				 "Note, we could update the simStack and spillBase here but that is done in restoreSimStackAtMergePoint:
  				 spilled ifFalse:
  					[simSpillBase := i - 1].
  				 simStack
  					at: i
  					put: (self
  							cCode: [mergeSimStack at: i]
  							inSmalltalk: [(mergeSimStack at: i) copy])"]]
  		ifFalse:
  			[simStackPtr to: methodOrBlockNumTemps by: -1 do:
  				[:i|
  				 currentEntry := self simStack: simStack at: i.
  				 targetEntry := self simStack: mergeSimStack at: i.
  				 writtenToRegisters := writtenToRegisters bitOr: targetEntry registerMask.
  				 (currentEntry reconcileForwardsWith: targetEntry) ifTrue:
  					[self assert: i >= methodOrBlockNumTemps.
  					 self deassignRegisterForTempVar: targetEntry in: mergeSimStack.
  					 targetEntry
  						type: SSRegister;
  						register: targetEntry liveRegister].
  				 "Note, we could update the simStack and spillBase here but that is done in restoreSimStackAtMergePoint:
  				 spilled ifFalse:
  					[simSpillBase := i - 1].
  				 simStack
  					at: i
  					put: (self
  							cCode: [mergeSimStack at: i]
  							inSmalltalk: [(mergeSimStack at: i) copy])"]].
  	"Note that since we've deassigned any conflicts beyond the temps above we need only compare the temps here."
  	methodOrBlockNumTemps - 1 to: 0 by: -1 do:
  		[:i|
  		 targetEntry := self simStack: mergeSimStack at: i.
  		 (targetEntry registerMask noMask: writtenToRegisters) ifTrue:
  			[currentEntry := self simStack: simStack at: i.
  			 writtenToRegisters := writtenToRegisters bitOr: targetEntry registerMask.
  			 (currentEntry reconcileForwardsWith: targetEntry) ifTrue:
+ 				[self assert: i >= methodOrBlockNumTemps.
- 				[self assert: i >= methodOrBlockNumArgs.
  				 self deassignRegisterForTempVar: targetEntry in: mergeSimStack]]].
  	optStatus isReceiverResultRegLive ifFalse:
  		[forwards
  			ifTrue: "a.k.a. fixup isReceiverResultRegSelf: (fixup isReceiverResultRegSelf and: [optStatus isReceiverResultRegLive])"
  				[fixup isReceiverResultRegSelf: false]
  			ifFalse:
  				[fixup isReceiverResultRegSelf ifTrue:
  					[self putSelfInReceiverResultReg]]]!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genExtEnsureAllocatableSlots (in category 'bytecode generators') -----
+ genExtEnsureAllocatableSlots
+ 	"SistaV1	*	236	11101100	iiiiiiii	Ensure Allocatable Slots (+ Extend A * 256)"
+ 	| slots skip |
+ 	slots := (extA bitShift: 8) + byte1.
+ 	extA := 0.
+ 	self
+ 		MoveAw: objectMemory freeStartAddress R: TempReg;
+ 		CmpCq: objectMemory getScavengeThreshold - (objectMemory bytesPerOop * slots) R: TempReg.
+ 	skip := self JumpAboveOrEqual: 0.
+ 	objectRepresentation genSetGCNeeded.
+ 	self CallRT: ceCheckForInterruptTrampoline.
+ 	skip jmpTarget: self Label.
+ 	self annotateBytecode: skip getJmpTarget.
+ 	^0!

Item was changed:
  ----- Method: SistaCogit>>genBinaryConstOpVarInlinePrimitive: (in category 'inline primitive generators') -----
  genBinaryConstOpVarInlinePrimitive: prim
  	"Const op var version of binary inline primitives."
  	"SistaV1: 248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution.
  	 See EncoderForSistaV1's class comment and StackInterpreter>>#binaryInlinePrimitive:"
  	<option: #SistaVM>
  	| ra val untaggedVal adjust |
  	ra := self allocateRegForStackEntryAt: 0.
  	self ssTop popToReg: ra.
  	self ssPop: 1.
  	val := self ssTop constant.
  	self ssPop: 1.
  	untaggedVal := val - objectMemory smallIntegerTag.
  	prim caseOf: {
  		"0 through 6, +, -, *, /, //, \\, quo:, SmallInteger op SmallInteger => SmallInteger, no overflow"
  		[0]	->	[self AddCq: untaggedVal R: ra].
  		[1]	->	[self MoveCq: val R: TempReg.
  				 self SubR: ra R: TempReg.
  				 objectRepresentation genAddSmallIntegerTagsTo: TempReg.
  				 self MoveR: TempReg R: ra].
  		[2]	->	[objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: ra.
  				 self MoveCq: untaggedVal R: TempReg.
  				 self MulR: TempReg R: ra.
  				 objectRepresentation genSetSmallIntegerTagsIn: ra].
  
+ 		"2011 through 2015	Variable-sized pointers new, byte new, 16-bit new, 32-bit new, 64-bit new"
+ 
  		"2016 through 2020, bitAnd:, bitOr:, bitXor, bitShiftLeft:, bitShiftRight:, SmallInteger op SmallInteger => SmallInteger, no overflow"
  		[16] -> [ self AndCq: val R: ra ].
  		[17] -> [ self OrCq: val R: ra ].
  		[18] -> [ self XorCw: untaggedVal R: ra. ].
  		[19] -> [ objectRepresentation genConvertSmallIntegerToIntegerInReg: ra.
  				 self MoveCq: untaggedVal R: TempReg.
  				 self LogicalShiftLeftR: ra R: TempReg.
  				 objectRepresentation genAddSmallIntegerTagsTo: TempReg.
  				 self MoveR: TempReg R: ra].
  		[20] ->	[objectRepresentation genConvertSmallIntegerToIntegerInReg: ra.
  				 self MoveCq: untaggedVal R: TempReg.
  				 self ArithmeticShiftRightR: ra R: TempReg.
  				 objectRepresentation genClearAndSetSmallIntegerTagsIn: TempReg.
  				 self MoveR: TempReg R: ra].
  
  		"2032	through 2037, >, <, >=, <=. =, ~=, SmallInteger op SmallInteger => Boolean (flags?? then in jump bytecodes if ssTop is a flags value, just generate the instruction!!!!)"
  		"CmpCqR is SubRCq so everything is reversed, but because no CmpRCq things are reversed again and we invert the sense of the jumps."
  		[32] -> [ self CmpCq: val R: ra.
  				self genBinaryInlineComparison: JumpLess opFalse: JumpGreaterOrEqual destReg: ra ].
  		[33] -> [ self CmpCq: val R: ra.
  				self genBinaryInlineComparison: JumpGreater opFalse: JumpLessOrEqual destReg: ra ].
  		[34] -> [ self CmpCq: val R: ra.
  				self genBinaryInlineComparison: JumpLessOrEqual opFalse: JumpGreater destReg: ra ].
  		[35] -> [ self CmpCq: val R: ra.
  				self genBinaryInlineComparison: JumpGreaterOrEqual opFalse: JumpLess destReg: ra ].
  		[36] -> [ self CmpCq: val R: ra.
  				self genBinaryInlineComparison: JumpZero opFalse: JumpNonZero destReg: ra ].
  		[37] -> [ self CmpCq: val R: ra.
  				self genBinaryInlineComparison: JumpNonZero opFalse: JumpZero destReg: ra ].
  
  		"2064	through 2068, Pointer Object>>at:, Byte Object>>at:, Short16 Word Object>>at: LongWord32 Object>>at: Quad64Word Object>>at:. obj op 0-rel SmallInteger => oop"
  		[64] ->	[objectRepresentation genConvertSmallIntegerToIntegerInReg: ra.
  				adjust := (objectMemory baseHeaderSize >> objectMemory shiftForWord) - 1. "shift by baseHeaderSize and then move from 1 relative to zero relative"
  				adjust ~= 0 ifTrue: [ self AddCq: adjust R: ra. ]. 
  				self genMoveConstant: val R: TempReg.
  				self MoveXwr: ra R: TempReg R: ra].
  		[65] ->	[objectRepresentation genConvertSmallIntegerToIntegerInReg: ra.
  				adjust := objectMemory baseHeaderSize - 1. "shift by baseHeaderSize and then move from 1 relative to zero relative"
  				self AddCq: adjust R: ra.
  				self genMoveConstant: val R: TempReg.
  				self MoveXbr: ra R: TempReg R: ra.
  				objectRepresentation genConvertIntegerToSmallIntegerInReg: ra]
  	}
  	otherwise: [^EncounteredUnknownBytecode].
  	self ssPushRegister: ra.
  	^0!

Item was changed:
  ----- Method: SistaMethodZone>>setCogCodeZoneThreshold: (in category 'accessing') -----
  setCogCodeZoneThreshold: ratio
  	<api>
  	<var: #ratio type: #double>
- 	self break.
  	(ratio >= 0.1 and: [ratio <= 1.0]) ifFalse:
  		[^PrimErrBadArgument].
  	thresholdRatio := ratio.
  	self computeAllocationThreshold.
  	^0!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager>>needGCFlagAddress (in category 'trampoline support') -----
+ needGCFlagAddress
+ 	<api>
+ 	<returnTypeC: #usqInt>
+ 	^self cCode: [(self addressOf: needGCFlag) asUnsignedInteger]
+ 		inSmalltalk: [cogit simulatedReadWriteVariableAddress: #needGCFlag in: self]!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>needGCFlagAddress (in category 'trampoline support') -----
+ needGCFlagAddress
+ 	<api>
+ 	<returnTypeC: #usqInt>
+ 	^self cCode: [(self addressOf: needGCFlag) asUnsignedInteger]
+ 		inSmalltalk: [cogit simulatedReadWriteVariableAddress: #needGCFlag in: self]!

Item was added:
+ ----- Method: SpurMemoryManager>>checkForAvailableSlots: (in category 'gc - scavenging') -----
+ checkForAvailableSlots: slots
+ 	"Check for slots worth of free space being available.  Answer if that many slots are available.
+ 	 If that many slots are not availabe, schedule a scavenge."
+ 	<inline: true>
+ 	freeStart + (self bytesPerOop * slots) <= scavengeThreshold ifTrue:
+ 		[^true].
+ 	needGCFlag := true.
+ 	^false!

Item was added:
+ ----- Method: StackDepthFinder>>ensureAllocateableSlots: (in category 'as yet unclassified') -----
+ ensureAllocateableSlots: numSlots
+ 	"nothing to do here..."!

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."
  
  	initializationOptions at: #SistaV1BytecodeSet put: (SistaV1BytecodeSet := true).
  
  	BytecodeTable := Array new: 256.
  	BytecodeEncoderClassName := #EncoderForSistaV1.
  	BytecodeSetHasDirectedSuperSend := true.
  	BytecodeSetHasExtensions := true.
  	LongStoreBytecode := 245.
  	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	 bytecodePrimNotIdenticalSistaV1) "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		unknownBytecode)
  		(231		pushNewArrayBytecode)
  		(232		extPushIntegerBytecode)
  		(233		extPushCharacterBytecode)
  
  		(234		extSendBytecode)
  		(235		extSendSuperBytecode)
  
+ 		(236		extEnsureAllocatableSlots)
- 		(236		unknownBytecode)
  
  		(237		extUnconditionalJump)
  		(238		extJumpIfTrue)
  		(239		extJumpIfFalse)
  
  		(240		extSistaStoreAndPopReceiverVariableBytecode)
  		(241		extSistaStoreAndPopLiteralVariableBytecode)
  		(242		longStoreAndPopTemporaryVariableBytecode)
  
  		(243		extSistaStoreReceiverVariableBytecode)
  		(244		extSistaStoreLiteralVariableBytecode)
  		(245		longStoreTemporaryVariableBytecode)
  
  		(246 247	unknownBytecode)
  
  		"3 byte bytecodes"
  		(248		callPrimitiveBytecode)
  		(249		extPushFullClosureBytecode)
  
  		(250		extPushClosureBytecode)
  		(251		extPushRemoteTempOrInstVarLongBytecode)
  		(252		extStoreRemoteTempOrInstVarLongBytecode)
  		(253		extStoreAndPopRemoteTempOrInstVarLongBytecode)
  				
  		(254		extJumpIfNotInstanceOfBehaviorsBytecode)
  
  		(255		unknownBytecode)
  	)!

Item was added:
+ ----- Method: StackInterpreter>>extEnsureAllocatableSlots (in category 'miscellaneous bytecodes') -----
+ extEnsureAllocatableSlots
+ 	"SistaV1		*	236		11101100	iiiiiiii		Ensure Allocatable Slots (+ Extend A * 256)"
+ 	| slots ok |
+ 	slots := (extA bitShift: 8) + self fetchByte.
+ 	self fetchNextBytecode.
+ 	extA := 0.
+ 	ok := objectMemory checkForAvailableSlots: slots.
+ 	ok ifFalse:
+ 		[self externalizeIPandSP.
+ 		 self checkForEventsMayContextSwitch: true.
+ 		 self browserPluginReturnIfNeeded.
+ 		 self internalizeIPandSP]!

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.
  	NumSpecialSelectors := 32.
  	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 isInstVarRef		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 120 genSpecialSelectorNotEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 121 127 genSpecialSelectorSend isMapped) "#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:)
  		(1 200 207 genStoreAndPopReceiverVariableBytecode isInstVarRef is1ByteInstVarStore isMappedIfImmutability needsFrameIfImmutability: -1)
  		
  		(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 isInstVarRef)		"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 unknownBytecode)
  		(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 genExtEnsureAllocatableSlots isMapped)
- 		(2 236 236 unknownBytecode)
  
  		"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 genSistaExtStoreAndPopReceiverVariableBytecode isInstVarRef isMappedIfImmutability)
  		(2 241 241 genSistaExtStoreAndPopLiteralVariableBytecode isMappedIfImmutability)
  		(2 242 242 genLongStoreAndPopTemporaryVariableBytecode)
  		(2 243 243 genSistaExtStoreReceiverVariableBytecode isInstVarRef isMappedIfImmutability)
  		(2 244 244 genSistaExtStoreLiteralVariableBytecode isMappedIfImmutability)
  		(2 245 245 genLongStoreTemporaryVariableBytecode)
  
  		(2 246 247	unknownBytecode)
  
  		"3 byte bytecodes"
  		(3 248 248 genCallPrimitiveBytecode)
  		(3 249 249 genExtPushFullClosureBytecode)
  		(3 250 250 genExtPushClosureBytecode block v4:Block:Code:Size:)
  		(3 251 251 genExtPushRemoteTempOrInstVarLongBytecode)
  		(3 252 252 genExtStoreRemoteTempOrInstVarLongBytecode isMappedIfImmutability)
  		(3 253 253 genExtStoreAndPopRemoteTempOrInstVarLongBytecode isMappedIfImmutability)
  
  		(3 254 254	genExtJumpIfNotInstanceOfBehaviorsBytecode branch v4:Long:BranchIfNotInstanceOf:Distance:)
  		
  		(3 255 255	unknownBytecode))!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>assertCorrectSimStackPtr (in category 'compile abstract instructions') -----
  assertCorrectSimStackPtr
  	<inline: true> "generates nothing anyway"
  	 self cCode: '' inSmalltalk:
  		[deadCode ifFalse:
  			[self assert: simStackPtr + (needsFrame ifTrue: [0] ifFalse: [1])
+ 						= (self debugStackPointerFor: bytecodePC)]].
- 						= (self debugStackPointerFor: bytecodePC)].
- 		 self deny: self duplicateRegisterAssignmentsInTemporaries].
  	!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genExtEnsureAllocatableSlots (in category 'bytecode generators') -----
+ genExtEnsureAllocatableSlots
+ 	"SistaV1	*	236	11101100	iiiiiiii	Ensure Allocatable Slots (+ Extend A * 256)"
+ 	self ssFlushTo: simStackPtr.
+ 	^super genExtEnsureAllocatableSlots!



More information about the Vm-dev mailing list