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

commits at source.squeak.org commits at source.squeak.org
Thu Sep 25 01:15:54 UTC 2014


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

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

Name: VMMaker.oscog-eem.882
Author: eem
Time: 24 September 2014, 6:12:31.37 pm
UUID: f22a00ff-acaf-49b0-9f6d-44efec689c0d
Ancestors: VMMaker.oscog-eem.881

Spur:
Fix bug in sweepToFollowForwardersForPigCompact
which failed to update and answer lowest forwarder.
Fixes numForwarders == 0 assert failures.

Fix bug with become and class table not removing
classes which become causes them to be unhashed.

Fix bogus assert fail in synchronousSignal:. Refactor
following code into ensureSemaphoreForwardedThroughContext:
and fix the assert there-in.

Use rawOverflowSlotsOf: in bytesInObject:.

Make a little more progress on Spur image segment
support.  Provide a classTableEntriesDo: and use it
to compute an arrayOfUnmarkedClasses.

Cogit:
Make sure voidImplicitReceiverCacheAt: sets
codeModified if IRCs are inline.

Make sure freeMethod: clears cmRefersToYoung

Fix assert in cogitPostGCAction: that would fire
erroneously in Spur become.

Nuke some unneeded pruneYoungReferrers calls.

Factor-out send-site unlinking into
unlinkSendAt:targetMethod:sendTable:

Comment CogMethodZone.

Sista:
Rename ceClassTrap: et al to ceSistaTrap: given
that Sista may trap in more cases than just unknown
classes.

Renumber the primitives in StackInterpreter>>
callPrimitiveBytecode. (bring them up-to-date)

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

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

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

Item was changed:
  ----- Method: CoInterpreter>>synchronousSignal: (in category 'process primitive support') -----
  synchronousSignal: aSemaphore 
  	"Signal the given semaphore from within the interpreter.
  	 Answer if the current process was preempted.
  	 Override to add tracing info."
  	| excessSignals |
  	<inline: false>
  	(self isEmptyList: aSemaphore) ifTrue:
  		["no process is waiting on this semaphore"
  		 excessSignals := self fetchInteger: ExcessSignalsIndex ofObject: aSemaphore.
  		 self storeInteger: ExcessSignalsIndex
  			ofObject: aSemaphore
  			withValue: excessSignals + 1.
  		 ^false].
  
+ 	objectMemory ensureSemaphoreForwardedThroughContext: aSemaphore.
- 	objectMemory hasSpurMemoryManagerAPI ifTrue:
- 		[| firstLink |
- 		 firstLink := objectMemory fetchPointer: FirstLinkIndex ofObject: aSemaphore.
- 		 (objectMemory isForwarded: firstLink) ifTrue:
- 			["0 = aSemaphore, 1 = aProcess. Hence reference to suspendedContext will /not/ be forwarded."
- 			 objectMemory followForwardedObjectFields: aSemaphore toDepth: 1].
- 		 self assert: (objectMemory isForwarded: (objectMemory fetchPointer: SuspendedContextIndex ofObject: firstLink)) not].
  
  	^self resume: (self removeFirstLinkOfList: aSemaphore)
  		preemptedYieldingIf: preemptionYields
  		from: CSSignal!

Item was changed:
  CogClass subclass: #CogMethodZone
  	instanceVariableNames: 'youngReferrers methodCount openPICList mzFreeStart baseAddress limitAddress methodBytesFreedSinceLastCompaction coInterpreter objectRepresentation cogit objectMemory unpairedMethodList'
  	classVariableNames: ''
  	poolDictionaries: 'CogMethodConstants VMBasicConstants'
  	category: 'VMMaker-JIT'!
  
+ !CogMethodZone commentStamp: 'eem 9/24/2014 15:59' prior: 0!
+ I am a simple allocator/deallocator for the native code zone.  I also manage the youngReferers list, which contains methods that may refer to one or more young objects, and the openPICList which is a linked list of all open PICs in the zone.
+ 
+ Instance Variables
+ 	baseAddress:								<Integer address>
+ 	coInterpreter:								<CoInterpreter>
+ 	cogit:										<Cogit>
+ 	limitAddress:								<Integer address>
+ 	methodBytesFreedSinceLastCompaction:	<Integer>
+ 	methodCount:								<Integer>
+ 	mzFreeStart:								<Integer address>
+ 	objectMemory:								<NewCoObjectMemory|SpurCoMemoryManager>
+ 	objectRepresentation:						<CogObjectRepresentation:>
+ 	openPICList:								<CogMethod *|nil>
+ 	unpairedMethodList:						<CogMethod *|nil>
+ 	youngReferrers:							<Integer address>
+ 
+ baseAddress
+ 	- the lowest address in the native method zone
+ 
+ coInterpreter
+ 	- simulation-only
+ 
+ cogit
+ 	- simulation-only
+ 
+ limitAddress
+ 	- the address immediately following the native method zone
+ 
+ methodBytesFreedSinceLastCompaction
+ 	- a count of the bytes in methods freed since the last compaction of the native method zone, used to answer the used bytes in the zone
+ 
+ methodCount
+ 	- a count of the number of methods in the native method zone
+ 
+ mzFreeStart
+ 	- the start of free space in the zone
+ 
+ objectMemory
+ 	- simulation-only
+ 
+ objectRepresentation
+ 	- simulation-only
+ 
+ openPICList
+ 	- the head of the list of open PICs
+ 
+ unpairedMethodList
+ 	- the head of the list of Cog methods with no associated CompiledMethod object (Newspeak only)
+ 
+ youngReferrers
+ 	- the pointer to the start of an array of pointers to CogMethods that refer to young objects.  May contain false positives.  Occupies the top of the zone from youngReferrers up to limitAddress
+ !
- !CogMethodZone commentStamp: '<historical>' prior: 0!
- I am a simple allocator/deallocator for the native code zone.  I also manage the youngReferers list, which contains methods that may refer to one or more young objects, and the openPICList which is a linked list of all open PICs in the zone.!

Item was changed:
  ----- Method: CogMethodZone>>freeMethod: (in category 'compaction') -----
  freeMethod: cogMethod
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: false>
  	self assert: cogMethod cmType ~= CMFree.
  	self assert: ((cogit cogMethodDoesntLookKosher: cogMethod) = 0
  				 or: [(cogit cogMethodDoesntLookKosher: cogMethod) = 23
  					 and: [(cogit cCoerceSimple: cogMethod methodObject to: #'CogMethod *') cmType = CMFree]]).
  	cogMethod cmType = CMMethod ifTrue:
  		["For non-Newspeak there should ne a one-to-one mapping between bytecoded and
  		  cog methods.  For Newspeak not necessarily, but only for anonymous accessors."
  		"Only reset the original method's header if it is referring to this CogMethod."
  		 (coInterpreter rawHeaderOf: cogMethod methodObject) asInteger = cogMethod asInteger
  			ifTrue:
  				[coInterpreter rawHeaderOf: cogMethod methodObject put: cogMethod methodHeader.
  				 self cppIf: NewspeakVM ifTrue:
  					[(objectRepresentation canPinObjects and: [cogMethod nextMethodOrIRCs ~= 0]) ifTrue:
  						[objectRepresentation freeIRCs: cogMethod nextMethodOrIRCs]]]
  			ifFalse:
  				[self assert: (cogit noAssertMethodClassAssociationOf: cogMethod methodObject) = objectMemory nilObject.
  				 self cppIf: NewspeakVM ifTrue:
  					[self removeFromUnpairedMethodList: cogMethod]].
+ 		 cogit maybeFreeCountersOf: cogMethod].
- 		 cogit maybeFreeCountersOf: cogMethod.
- 		 cogMethod cmRefersToYoung: false].
  	cogMethod cmType = CMOpenPIC ifTrue:
+ 		[self removeFromOpenPICList: cogMethod].
+ 	cogMethod cmRefersToYoung: false.
- 		[self removeFromOpenPICList: cogMethod.
- 		 cogMethod cmRefersToYoung: false].
  	cogMethod cmType: CMFree.
  	methodBytesFreedSinceLastCompaction := methodBytesFreedSinceLastCompaction
  												+ cogMethod blockSize!

Item was changed:
  ----- Method: CogMethodZone>>printCogYoungReferrers (in category 'printing') -----
  printCogYoungReferrers
  	<api>
  	<returnTypeC: #void>
  	| pointer cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	pointer := youngReferrers.
  	[pointer < limitAddress] whileTrue:
  		[cogMethod := coInterpreter cCoerceSimple: (objectMemory longAt: pointer) to: #'CogMethod *'.
  		 cogMethod cmRefersToYoung ifFalse:
+ 			[coInterpreter print: '*'].
+ 		 cogMethod cmType = CMFree ifTrue:
+ 			[coInterpreter print: '!!'].
+ 		 (cogMethod cmRefersToYoung and: [cogMethod cmType ~= CMFree]) ifFalse:
+ 			[coInterpreter print: ' '].
- 			[coInterpreter print: '* '].
  		 coInterpreter printCogMethod: cogMethod.
  		 pointer := pointer + BytesPerWord]!

Item was changed:
  ----- Method: Cogit>>cogitPostGCAction: (in category 'jit - api') -----
  cogitPostGCAction: gcMode
  	<api>
  	(gcMode = GCModeFull
  	 and: [objectRepresentation allYoungObjectsAgeInFullGC]) ifTrue:
  		[methodZone voidYoungReferrersPostTenureAll].
  	"Post-GC update every full method's objectHeader to whatever it needs to be"
  	self assert: self allMethodsHaveCorrectHeader.
+ 	"The youngReferrers should be correct after a GC since that is the point at which it is
+ 	 pruned.  But at other times false positives or free methods on the list are acceptable."
+ 	self assert: (gcMode = GCModeBecome or: [methodZone kosherYoungReferrers])!
- 	self assert: methodZone kosherYoungReferrers!

Item was changed:
  ----- Method: Cogit>>followForwardedMethods (in category 'garbage collection') -----
  followForwardedMethods
  	<api>
  	<option: #SpurObjectMemory>
  	<var: #cogMethod type: #'CogMethod *'>
  	| cogMethod freedPIC |
  	<var: #cogMethod type: #'CogMethod *'>
  	freedPIC := false.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[cogMethod cmType = CMMethod ifTrue:
  			[(objectMemory isForwarded: cogMethod methodObject) ifTrue:
  				[cogMethod methodObject: (objectMemory followForwarded: cogMethod methodObject).
  				 (objectMemory isYoungObject: cogMethod methodObject) ifTrue:
  					[methodZone ensureInYoungReferrers: cogMethod]]].
  		 cogMethod cmType = CMClosedPIC ifTrue:
  			[(self followMethodReferencesInClosedPIC: cogMethod) ifTrue:
  				[freedPIC := true.
  				 methodZone freeMethod: cogMethod]].
  		 cogMethod := methodZone methodAfter: cogMethod].
  	freedPIC ifTrue:
+ 		[self unlinkSendsToFree]!
- 		[self unlinkSendsToFree.
- 		 methodZone pruneYoungReferrers.
- 		 processor flushICacheFrom: codeBase to: methodZone limitZony asInteger]!

Item was changed:
  ----- Method: Cogit>>freeUnmarkedMachineCode (in category 'jit - api') -----
  freeUnmarkedMachineCode
  	"Free machine-code methods whose compiled methods are unmarked
  	 and open PICs whose selectors are not marked."
  	<api>
  	<option: #SpurObjectMemory>
  	| cogMethod freedMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	freedMethod := false.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[(cogMethod cmType = CMMethod
  		  and: [(objectMemory isMarked: cogMethod methodObject) not]) ifTrue:
  			[freedMethod := true.
  			 methodZone freeMethod: cogMethod].
  		 (cogMethod cmType = CMOpenPIC
  		  and: [(objectMemory isImmediate: cogMethod selector) not
  		  and: [(objectMemory isMarked: cogMethod selector) not]]) ifTrue:
  			[freedMethod := true.
  			 methodZone freeMethod: cogMethod].
  		 cogMethod := methodZone methodAfter: cogMethod].
  	freedMethod ifTrue:
+ 		[self unlinkSendsToFree]!
- 		[self unlinkSendsToFree.
- 		 methodZone pruneYoungReferrers.
- 		 processor flushICacheFrom: codeBase to: methodZone limitZony asInteger]!

Item was changed:
  ----- Method: Cogit>>mapObjectReferencesInMachineCodeForBecome (in category 'garbage collection') -----
  mapObjectReferencesInMachineCodeForBecome
  	"Update all references to objects in machine code for a become.
  	 Unlike incrementalGC or fullGC a method that does not refer to young may
  	 refer to young as a result of the become operation.  Unlike incrementalGC
  	 or fullGC the reference from a Cog method to its methodObject *must not*
  	 change since the two are two halves of the same object."
  	| cogMethod hasYoungObj hasYoungObjPtr freedPIC |
  	<var: #cogMethod type: #'CogMethod *'>
  	hasYoungObj := false.
  	hasYoungObjPtr := (self addressOf: hasYoungObj put: [:val| hasYoungObj := val]) asInteger.
  	codeModified := freedPIC := false.
  	self mapObjectReferencesInGeneratedRuntime.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[self assert: hasYoungObj not.
  		 cogMethod cmType ~= CMFree ifTrue:
  			[self assert: (self cogMethodDoesntLookKosher: cogMethod) = 0.
  			 cogMethod selector: (objectRepresentation remapOop: cogMethod selector).
  			 cogMethod cmType = CMClosedPIC
  				ifTrue:
  					[((objectMemory isYoung: cogMethod selector)
  					   or: [self mapObjectReferencesInClosedPIC: cogMethod]) ifTrue:
  						[freedPIC := true.
  						 methodZone freeMethod: cogMethod]]
  				ifFalse:
  					[(objectMemory isYoung: cogMethod selector) ifTrue:
  						[hasYoungObj := true].
  					 cogMethod cmType = CMMethod ifTrue:
  						[| remappedMethod |
  						 self assert: cogMethod objectHeader = objectMemory nullHeaderForMachineCodeMethod.
  						 remappedMethod := objectRepresentation remapOop: cogMethod methodObject.
  						 remappedMethod ~= cogMethod methodObject ifTrue:
  							[(coInterpreter methodHasCogMethod: remappedMethod) ifTrue:
  								[self error: 'attempt to become two cogged methods'].
  							 (objectMemory
  									withoutForwardingOn: cogMethod methodObject
  									and: remappedMethod
  									with: cogMethod cmUsesPenultimateLit
  									sendToCogit: #method:hasSameCodeAs:checkPenultimate:) ifFalse:
  								[self error: 'attempt to become cogged method into different method'].
  							 "For non-Newspeak there should ne a one-to-one mapping between bytecoded and
  							  cog methods.  For Newspeak not necessarily, but only for anonymous accessors."
  							 "Only reset the method object's header if it is referring to this CogMethod."
  							 (coInterpreter rawHeaderOf: cogMethod methodObject) = cogMethod asInteger
  								ifTrue:
  									[coInterpreter
  										rawHeaderOf: cogMethod methodObject
  										put: cogMethod methodHeader.
  									 cogMethod
  										methodHeader: (coInterpreter rawHeaderOf: remappedMethod);
  										methodObject: remappedMethod.
  									 coInterpreter
  										rawHeaderOf: remappedMethod
  										put: cogMethod asInteger]
  								ifFalse:
  									[self assert: (self noAssertMethodClassAssociationOf: cogMethod methodObject)
  													= objectMemory nilObject.
  									 cogMethod
  										methodHeader: (coInterpreter rawHeaderOf: remappedMethod);
  										methodObject: remappedMethod]].
  						 (objectMemory isYoung: cogMethod methodObject) ifTrue:
  							[hasYoungObj := true]].
  					 self mapFor: cogMethod
  						 performUntil: #remapIfObjectRef:pc:hasYoung:
  						 arg: hasYoungObjPtr.
  					 hasYoungObj
  						ifTrue:
  							[methodZone ensureInYoungReferrers: cogMethod.
  							hasYoungObj := false]
  						ifFalse:
  							[cogMethod cmRefersToYoung: false]]].
  		cogMethod := methodZone methodAfter: cogMethod].
- 	methodZone pruneYoungReferrers.
  	freedPIC ifTrue:
+ 		[self unlinkSendsToFree].
- 		[self unlinkSendsToFree.
- 		 codeModified := true].
  	codeModified ifTrue: "After updating oops in inline caches we need to flush the icache."
  		[processor flushICacheFrom: codeBase to: methodZone limitZony asInteger]!

Item was changed:
  ----- Method: Cogit>>markLiteralsAndUnlinkIfUnmarkedSend:pc:method: (in category 'garbage collection') -----
  markLiteralsAndUnlinkIfUnmarkedSend: annotation pc: mcpc method: cogMethod
  	"Mark and trace literals.  Unlink sends that have unmarked cache tags or targets."
  	<var: #mcpc type: #'char *'>
  	| literal |
  	annotation = IsObjectReference ifTrue:
  		[literal := backEnd literalBeforeFollowingAddress: mcpc asUnsignedInteger.
  		 (objectRepresentation
  				markAndTraceLiteral: literal
  				in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
  				atpc: mcpc asUnsignedInteger) ifTrue:
  			[codeModified := true]].
  	(self isSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj | | cacheTagMarked |
  			 cacheTagMarked := tagCouldBeObj and: [objectRepresentation cacheTagIsMarked: cacheTag].
  			 entryPoint > methodZoneBase
  				ifTrue: "It's a linked send."
  					[self targetMethodAndSendTableFor: entryPoint into:
+ 						[:targetMethod :sendTable| 
- 						[:targetMethod :sendTable| | unlinkedRoutine |
  						 (cacheTagMarked not
  						  or: [self markAndTraceOrFreeCogMethod: targetMethod
  								firstVisit: targetMethod asUnsignedInteger > mcpc asUnsignedInteger]) ifTrue:
  							["Either the cacheTag is unmarked (e.g. new class) or the target
  							  has been freed (because it is unmarked), so unlink the send."
+ 							 self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable.
- 							 unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
- 							 backEnd
- 								rewriteInlineCacheAt: mcpc asInteger
- 								tag: targetMethod selector
- 								target: unlinkedRoutine.
- 							 codeModified := true.
  							 objectRepresentation
  								markAndTraceLiteral: targetMethod selector
  								in: targetMethod
  								at: (self addressOf: targetMethod selector put: [:val| targetMethod selector: val])]]]
  				ifFalse:  "cacheTag is selector"
  					[(objectRepresentation
  							markAndTraceCacheTagLiteral: cacheTag
  							in: cogMethod
  							atpc: mcpc asUnsignedInteger) ifTrue:
  						[codeModified := true].
  					 self cppIf: NewspeakVM ifTrue:
  						[entryPoint = ceImplicitReceiverTrampoline ifTrue:
  							[| cacheAddress class mixin |
  							 (objectRepresentation
  									markAndTraceCacheTagLiteral: cacheTag
  									in: cogMethod
  									atpc: mcpc asUnsignedInteger) ifTrue:
  								[codeModified := true].  "cacheTag is selector"
  							 self assert: NumOopsPerIRC = 2.
  							 cacheAddress := self implicitReceiverCacheAddressAt: mcpc.
  							 (class := backEnd unalignedLongAt: cacheAddress) ~= 0
  								ifTrue:
  									[(objectRepresentation cacheTagIsMarked: class)
  										ifTrue:
  											[(mixin := backEnd unalignedLongAt: cacheAddress + BytesPerOop) ~= 0 ifTrue:
  												[objectRepresentation
  													markAndTraceLiteral: mixin
  													in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
  													at: (self asAddress: cacheAddress + BytesPerOop
  															put: [:val| backEnd unalignedLongAt: cacheAddress + BytesPerOop put: val])]]
  										ifFalse:
  											[backEnd
  												unalignedLongAt: cacheAddress put: 0;
  												unalignedLongAt: cacheAddress + BytesPerOop put: 0.
  											 codeModified := true]]
  								ifFalse:
  									[self assert: (backEnd unalignedLongAt: cacheAddress + BytesPerOop) = 0]]]]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>unlinkIfFreeOrLinkedSend:pc:of: (in category 'in-line cacheing') -----
  unlinkIfFreeOrLinkedSend: annotation pc: mcpc of: theSelector
  	<var: #mcpc type: #'char *'>
  	| entryPoint |
  	(self isSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase
  			ifTrue: "It's a linked send."
  				[self targetMethodAndSendTableFor: entryPoint into:
+ 					[:targetMethod :sendTable| 
- 					[:targetMethod :sendTable| | unlinkedRoutine |
  					 (targetMethod cmType = CMFree
  					  or: [targetMethod selector = theSelector]) ifTrue:
+ 						[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]
- 						[unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
- 						 backEnd
- 							rewriteInlineCacheAt: mcpc asInteger
- 							tag: targetMethod selector
- 							target: unlinkedRoutine.
- 						 codeModified := true]]]
  			ifFalse:
  				[self cppIf: NewspeakVM ifTrue:
  					[(entryPoint = ceImplicitReceiverTrampoline
  					 and: [(backEnd inlineCacheTagAt: mcpc asInteger) = theSelector]) ifTrue:
  					 	[self voidImplicitReceiverCacheAt: mcpc]]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>unlinkIfLinkedSend:pc:ignored: (in category 'in-line cacheing') -----
  unlinkIfLinkedSend: annotation pc: mcpc ignored: superfluity
  	<var: #mcpc type: #'char *'>
  	| entryPoint |
  	(self isSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase
  			ifTrue: "It's a linked send."
  				[self targetMethodAndSendTableFor: entryPoint into:
+ 					[:targetMethod :sendTable| 
+ 					 self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]
- 					[:targetMethod :sendTable| | unlinkedRoutine |
- 					 unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
- 					 backEnd
- 						rewriteInlineCacheAt: mcpc asInteger
- 						tag: targetMethod selector
- 						target: unlinkedRoutine]]
  			ifFalse:
  				[self cppIf: NewspeakVM ifTrue:
  					[entryPoint = ceImplicitReceiverTrampoline ifTrue:
  						[self voidImplicitReceiverCacheAt: mcpc]]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>unlinkIfLinkedSend:pc:of: (in category 'in-line cacheing') -----
  unlinkIfLinkedSend: annotation pc: mcpc of: theSelector
  	<var: #mcpc type: #'char *'>
  	| entryPoint |
  	(self isSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase
  			ifTrue: "It's a linked send."
  				[self targetMethodAndSendTableFor: entryPoint into:
+ 					[:targetMethod :sendTable| 
- 					[:targetMethod :sendTable| | unlinkedRoutine |
  					 targetMethod selector = theSelector ifTrue:
+ 						[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]
- 						[unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
- 						 backEnd
- 							rewriteInlineCacheAt: mcpc asInteger
- 							tag: targetMethod selector
- 							target: unlinkedRoutine.
- 						 codeModified := true]]]
  			ifFalse:
  				[self cppIf: NewspeakVM ifTrue:
  					[(entryPoint = ceImplicitReceiverTrampoline
  					  and: [(backEnd inlineCacheTagAt: mcpc asInteger) = theSelector]) ifTrue:
  						[self voidImplicitReceiverCacheAt: mcpc]]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>unlinkIfLinkedSend:pc:to: (in category 'in-line cacheing') -----
  unlinkIfLinkedSend: annotation pc: mcpc to: theCogMethod
  	<var: #mcpc type: #'char *'>
  	| entryPoint |
  	(self isSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase
  			ifTrue: "It's a linked send."
  				[self targetMethodAndSendTableFor: entryPoint into:
+ 					[:targetMethod :sendTable| 
- 					[:targetMethod :sendTable| | unlinkedRoutine |
  					 targetMethod asInteger = theCogMethod ifTrue:
+ 						[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]
- 						[unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
- 						 backEnd
- 							rewriteInlineCacheAt: mcpc asInteger
- 							tag: targetMethod selector
- 							target: unlinkedRoutine.
- 						 codeModified := true]]]
  			ifFalse: "Can't tell the target with PushReciver/SendImplicit so flush anyway."
  				[self cppIf: NewspeakVM ifTrue:
  					[entryPoint = ceImplicitReceiverTrampoline ifTrue:
  						[self voidImplicitReceiverCacheAt: mcpc]]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>unlinkIfLinkedSendToFree:pc:ignored: (in category 'in-line cacheing') -----
  unlinkIfLinkedSendToFree: annotation pc: mcpc ignored: superfluity
  	<var: #mcpc type: #'char *'>
  	| entryPoint |
  	(self isSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase ifTrue: "It's a linked send."
  			[self targetMethodAndSendTableFor: entryPoint into:
+ 				[:targetMethod :sendTable| 
- 				[:targetMethod :sendTable| | unlinkedRoutine |
  				 targetMethod cmType = CMFree ifTrue:
+ 					[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]].
- 					[unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
- 					 backEnd
- 						rewriteInlineCacheAt: mcpc asInteger
- 						tag: targetMethod selector
- 						target: unlinkedRoutine.
- 					 codeModified := true]]]].
  	^0 "keep scanning"!

Item was added:
+ ----- Method: Cogit>>unlinkSendAt:targetMethod:sendTable: (in category 'in-line cacheing') -----
+ unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable
+ 	<inline: true>
+ 	| unlinkedRoutine |
+ 	unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
+ 	backEnd
+ 		rewriteInlineCacheAt: mcpc asInteger
+ 		tag: targetMethod selector
+ 		target: unlinkedRoutine.
+ 	codeModified := true!

Item was changed:
  ----- Method: Cogit>>voidImplicitReceiverCacheAt: (in category 'newspeak support') -----
  voidImplicitReceiverCacheAt: mcpc
  	"Cached push implicit receiver implementation.  If objectRepresentation doesn't support
  	 pinning then caller looks like
  				mov selector, SendNumArgsReg
  				call ceImplicitReceiver
  				br continue
  		Lclass:	.word
  		Lmixin::	.word
  		continue:
  	 If objectRepresentation supports pinning then caller looks like
  				mov Lclass, Arg1Reg
  				mov selector, SendNumArgsReg
  				call ceImplicitReceiver
  	 and Lclass: .word; Lmixin: .word is somewhere on the heap."
  	<option: #NewspeakVM>
  	| cacheAddress |
  	self assert: NumOopsPerIRC = 2.
  	cacheAddress := self implicitReceiverCacheAddressAt: mcpc.
  	backEnd
  		unalignedLongAt: cacheAddress put: 0;
+ 		unalignedLongAt: cacheAddress + BytesPerOop put: 0.
+ 	objectRepresentation canPinObjects ifFalse:
+ 		[codeModified := true]!
- 		unalignedLongAt: cacheAddress + BytesPerOop put: 0!

Item was changed:
  ----- Method: ObjectMemory class>>initializeSpecialObjectIndices (in category 'initialization') -----
  initializeSpecialObjectIndices
  	"Initialize indices into specialObjects array."
  
  	NilObject := 0.
  	FalseObject := 1.
  	TrueObject := 2.
  	SchedulerAssociation := 3.
  	ClassBitmap := 4.
  	ClassSmallInteger := 5.
  	ClassByteString := ClassString := 6. "N.B.  Actually class ByteString"
  	ClassArray := 7.
  	"SmalltalkDictionary := 8."  "Do not delete!!"
  	ClassFloat := 9.
  	ClassMethodContext := 10.
  	ClassBlockContext := 11.
  	ClassPoint := 12.
  	ClassLargePositiveInteger := 13.
  	TheDisplay := 14.
  	ClassMessage := 15.
  	"ClassCompiledMethod := 16. unused by the VM"
  	TheLowSpaceSemaphore := 17.
  	ClassSemaphore := 18.
  	ClassCharacter := 19.
  	SelectorDoesNotUnderstand := 20.
  	SelectorCannotReturn := 21.
  	ProcessSignalingLowSpace := 22.	"was TheInputSemaphore"
  	SpecialSelectors := 23.
  	CharacterTable := 24.
  	SelectorMustBeBoolean := 25.
  	ClassByteArray := 26.
  	"ClassProcess := 27. unused"
  	CompactClasses := 28.
  	TheTimerSemaphore := 29.
  	TheInterruptSemaphore := 30.
  	SelectorCannotInterpret := 34.
  	"Was MethodContextProto := 35."
  	ClassBlockClosure := 36.
  	"Was BlockContextProto := 37."
  	ExternalObjectsArray := 38.
  	ClassMutex := 39.
  	"Was: ClassTranslatedMethod := 40."
  	ProcessInExternalCodeTag := 40.
  	TheFinalizationSemaphore := 41.
  	ClassLargeNegativeInteger := 42.
  
  	ClassExternalAddress := 43.
  	ClassExternalStructure := 44.
  	ClassExternalData := 45.
  	ClassExternalFunction := 46.
  	ClassExternalLibrary := 47.
  
  	SelectorAboutToReturn := 48.
  	SelectorRunWithIn := 49.
  
  	SelectorAttemptToAssign := 50.
  	"PrimErrTableIndex := 51. in VMClass class>>initializePrimitiveErrorCodes"
  	ClassAlien := 52.
  	SelectorInvokeCallback := 53.
  	ClassUnsafeAlien := 54.
  
  	ClassWeakFinalizer := 55.
  
  	ForeignCallbackProcess := 56.
  
  	SelectorUnknownBytecode := 57.
  	SelectorCounterTripped := 58.
+ 	SelectorSistaTrap := 59
- 	SelectorClassTrap := 59
  !

Item was added:
+ ----- Method: ObjectMemory>>ensureSemaphoreForwardedThroughContext: (in category 'forward compatibility') -----
+ ensureSemaphoreForwardedThroughContext: aSemaphore
+ 	"Compatibility with SpurMemoryManager"
+ 	<inline: true>!

Item was changed:
  StackToRegisterMappingCogit subclass: #SistaStackToRegisterMappingCogit
+ 	instanceVariableNames: 'picDataIndex picData numCounters counters counterIndex initialCounterValue ceTrapTrampoline'
- 	instanceVariableNames: 'picDataIndex picData numCounters counters counterIndex initialCounterValue ceClassTrapTrampoline'
  	classVariableNames: 'CounterBytes MaxCounterValue'
  	poolDictionaries: 'VMSqueakClassIndices'
  	category: 'VMMaker-JIT'!
  
  !SistaStackToRegisterMappingCogit commentStamp: 'eem 4/7/2014 12:23' prior: 0!
  A SistaStackToRegisterMappingCogit is a refinement of StackToRegisterMappingCogit that generates code suitable for dynamic optimization by Sista, the Speculative Inlining Smalltalk Architecture, a project by Clément Bera and Eliot Miranda.  Sista is an optimizer that exists in the Smalltalk image, /not/ in the VM,  and optimizes by substituting normal bytecoded methods by optimized bytecoded methods that may use special bytecodes for which the Cogit can generate faster code.  These bytecodes eliminate overheads such as bounds checks or polymorphic code (indexing Array, ByteArray, String etc).  But the bulk of the optimization performed is in inlining blocks and sends for the common path.
  
  The basic scheme is that SistaStackToRegisterMappingCogit generates code containing performance counters.  When these counters trip, a callback into the image is performed, at which point Sista analyses some portion of the stack, looking at performance data for the methods on the stack, and optimises based on the stack and performance data.  Execution then resumes in the optimized code.
  
  SistaStackToRegisterMappingCogit adds counters to conditional branches.  Each branch has an executed and a taken count, implemented at the two 16-bit halves of a single 32-bit word.  Each counter pair is initialized with initialCounterValue.  On entry to the branch the executed count is decremented and if the count goes below zero the ceMustBeBooleanAdd[True|False] trampoline called.  The trampoline distinguishes between true mustBeBoolean and counter trips because in the former the register temporarily holding the counter value will contain zero.  Then the condition is tested, and if the branch is taken the taken count is decremented.  The two counter values allow an optimizer to collect basic block execution paths and to know what are the "hot" paths through execution that are worth agressively optimizing.  Since conditional branches are about 1/6 as frequent as sends, and since they can be used to determine the hot path through code, they are a better choice to count than, for example, method or block entry.
  
  SistaStackToRegisterMappingCogit implements picDataFor:into: that fills an Array with the state of the counters in a method and the state of each linked send in a method.  This is used to implement a primitive used by the optimizer to answer the branch and send data for a method as an Array.
  
  Instance Variables
  	counterIndex:			<Integer>
  	counterMethodCache:	<CogMethod>
  	counters:				<Array of AbstractInstruction>
  	initialCounterValue:		<Integer>
  	numCounters:			<Integer>
  	picData:				<Integer Oop>
  	picDataIndex:			<Integer>
  	prevMapAbsPCMcpc:	<Integer>
  
  counterIndex
  	- xxxxx
  
  counterMethodCache
  	- xxxxx
  
  counters
  	- xxxxx
  
  initialCounterValue
  	- xxxxx
  
  numCounters
  	- xxxxx
  
  picData
  	- xxxxx
  
  picDataIndex
  	- xxxxx
  
  prevMapAbsPCMcpc
  	- xxxxx
  !

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genExtTrapIfNotInstanceOfBehaviorsBytecode (in category 'bytecode generators') -----
  genExtTrapIfNotInstanceOfBehaviorsBytecode
  	"SistaV1: *	236		11101100	iiiiiiii		Trap If Not Instance Of Behavior/Array Of Behavior #iiiiiiii (+ Extend A * 256, where Extend A >= 0)"
  	| reg litIndex literal branches label numBranches |
  	<var: #branches type: #'AbstractInstruction **'>
  	reg := self ssStorePop: true toPreferredReg: ReceiverResultReg.
  	reg ~= ReceiverResultReg ifTrue:
  		[self MoveR: reg R: ReceiverResultReg].
  	optStatus isReceiverResultRegLive: false.
  	litIndex := extA * 256 + byte1.
  	extA := 0.
  	literal := self getLiteral: litIndex.
  	"Allow an extra branch for Spur, which may have two tag patterns for SmallInteger"
  	numBranches := (objectMemory isArrayNonImm: literal)
  						ifTrue: [(objectMemory numSlotsOf: literal) + 1]
  						ifFalse: [2].
  	branches := self alloca: numBranches type: (self cCode: [#'AbstractInstruction *'] inSmalltalk: [backEnd class]).
  	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.
- 	self CallRT: ceClassTrapTrampoline.
  	label := self Label.
  	0 to: numBranches - 1 do:
  		[:i|
  		(branches at: i) jmpTarget: label].
  	^0!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>generateSistaRuntime (in category 'initialization') -----
  generateSistaRuntime
+ 	"Trap sends Sista trap message to context with top of stack, so we don't need any arguments..."
+ 	ceTrapTrampoline := self genTrampolineFor: #ceSistaTrap:
+ 									called: 'ceSistaTrapTrampoline'
- 	"Class trap sends class trap message to context with top of stack, so we on't need any arguments..."
- 	ceClassTrapTrampoline := self genTrampolineFor: #ceClassTrap:
- 									called: 'ceClassTrapTrampoline'
  									arg: ReceiverResultReg!

Item was changed:
  ----- Method: Spur32BitMemoryManager>>bytesInObject: (in category 'object enumeration') -----
  bytesInObject: objOop
  	"Answer the total number of bytes in an object including header and possible overflow size header."
  	<returnTypeC: #usqInt>
  	| headerNumSlots numSlots |
  	headerNumSlots := self rawNumSlotsOf: objOop.
  	numSlots := headerNumSlots = self numSlotsMask
+ 					ifTrue: [self rawOverflowSlotsOf: objOop]
- 					ifTrue: [self longAt: objOop - self baseHeaderSize]
  					ifFalse: [headerNumSlots = 0 ifTrue: [1] ifFalse: [headerNumSlots]].
  	^numSlots + (numSlots bitAnd: 1) << self shiftForWord
  	+ (headerNumSlots = self numSlotsMask
  		ifTrue: [self baseHeaderSize + self baseHeaderSize]
  		ifFalse: [self baseHeaderSize])!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>bytesInObject: (in category 'object enumeration') -----
  bytesInObject: objOop
  	"Answer the total number of bytes in an object including header and possible overflow size header."
  	<returnTypeC: #usqInt>
  	| header headerNumSlots numSlots |
  	<var: 'header' type: #usqLong>
  	self flag: #endianness.
  	header := self longAt: objOop.
  	headerNumSlots := header >> self numSlotsFullShift.
  	numSlots := headerNumSlots = self numSlotsMask
+ 					ifTrue: [self rawOverflowSlotsOf: objOop]
- 					ifTrue: [header bitAnd: 16rFFFFFFFFFFFFFF]
  					ifFalse: [headerNumSlots = 0 ifTrue: [1] ifFalse: [headerNumSlots]].
  	^numSlots << self shiftForWord
  	+ (headerNumSlots = self numSlotsMask
  		ifTrue: [self baseHeaderSize + self baseHeaderSize]
  		ifFalse: [self baseHeaderSize])!

Item was changed:
  CogClass subclass: #SpurMemoryManager
(excessive size, no diff calculated)

Item was changed:
  ----- Method: SpurMemoryManager class>>initializeSpecialObjectIndices (in category 'class initialization') -----
  initializeSpecialObjectIndices
  	"Initialize indices into specialObjects array."
  
  	NilObject := 0.
  	FalseObject := 1.
  	TrueObject := 2.
  	SchedulerAssociation := 3.
  	ClassBitmap := 4.
  	ClassSmallInteger := 5.
  	ClassByteString := ClassString := 6. "N.B.  Actually class ByteString"
  	ClassArray := 7.
  	"SmalltalkDictionary := 8."  "Do not delete!!"
  	ClassFloat := 9.
  	ClassMethodContext := 10.
  	"ClassBlockContext := 11. unused by the VM"
  	ClassPoint := 12.
  	ClassLargePositiveInteger := 13.
  	TheDisplay := 14.
  	ClassMessage := 15.
  	"ClassCompiledMethod := 16. unused by the VM"
  	TheLowSpaceSemaphore := 17.
  	ClassSemaphore := 18.
  	ClassCharacter := 19.
  	SelectorDoesNotUnderstand := 20.
  	SelectorCannotReturn := 21.
  	ProcessSignalingLowSpace := 22.	"was TheInputSemaphore"
  	SpecialSelectors := 23.
  	CharacterTable := nil.	"Must be unused by the VM"
  	SelectorMustBeBoolean := 25.
  	ClassByteArray := 26.
  	"ClassProcess := 27. unused"
  	CompactClasses := 28.
  	TheTimerSemaphore := 29.
  	TheInterruptSemaphore := 30.
  	SelectorCannotInterpret := 34.
  	"Was MethodContextProto := 35."
  	ClassBlockClosure := 36.
  	"Was BlockContextProto := 37."
  	ExternalObjectsArray := 38.
  	ClassMutex := 39.
  	"Was: ClassTranslatedMethod := 40."
  	ProcessInExternalCodeTag := 40.
  	TheFinalizationSemaphore := 41.
  	ClassLargeNegativeInteger := 42.
  
  	ClassExternalAddress := 43.
  	ClassExternalStructure := 44.
  	ClassExternalData := 45.
  	ClassExternalFunction := 46.
  	ClassExternalLibrary := 47.
  
  	SelectorAboutToReturn := 48.
  	SelectorRunWithIn := 49.
  
  	SelectorAttemptToAssign := 50.
  	"PrimErrTableIndex := 51. in VMClass class>>initializePrimitiveErrorCodes"
  	ClassAlien := 52.
  	SelectorInvokeCallback := 53.
  	ClassUnsafeAlien := 54.
  
  	ClassWeakFinalizer := 55.
  
  	ForeignCallbackProcess := 56.
  
  	SelectorUnknownBytecode := 57.
  	SelectorCounterTripped := 58.
+ 	SelectorSistaTrap := 59!
- 	SelectorClassTrap := 59!

Item was added:
+ ----- Method: SpurMemoryManager>>arrayOfUnmarkedClasses (in category 'image segment in/out') -----
+ arrayOfUnmarkedClasses
+ 	| nClasses classes i |
+ 	nClasses := 0.
+ 	self classTableEntriesDo:
+ 		[:class :ignored|
+ 		 (self isMarked: class) ifFalse:
+ 			[nClasses := nClasses + 1]].
+ 	nClasses = 0 ifTrue:
+ 		[^nilObj].
+ 	classes := self allocateSlots: nClasses format: self arrayFormat classIndex: ClassArrayCompactIndex.
+ 	classes ifNil:
+ 		[^self integerObjectOf: PrimErrNoMemory].
+ 	i := 0.
+ 	self classTableEntriesDo:
+ 		[:class :ignored|
+ 		 (self isMarked: class) ifFalse:
+ 			[self storePointer: i ofObject: classes withValue: class.
+ 			 i := i + 1]].
+ 	self assert: nClasses = i.
+ 	^classes!

Item was added:
+ ----- Method: SpurMemoryManager>>classTableEntriesDo: (in category 'class table') -----
+ classTableEntriesDo: binaryBlock
+ 	"Evaluate binaryBlock with all non-nil entries in the classTable and their index."
+ 	<inline: true>
+ 	0 to: numClassTablePages - 1 do:
+ 		[:i| | page |
+ 		 page := self fetchPointer: i ofObject: hiddenRootsObj.
+ 		 0 to: self classTablePageSize - 1 do:
+ 			[:j| | classOrNil |
+ 			classOrNil := self fetchPointer: j ofObject: page.
+ 			classOrNil ~= nilObj ifTrue:
+ 				[binaryBlock
+ 					value: classOrNil
+ 					value: i << self classTableMajorIndexShift + j]]]!

Item was added:
+ ----- Method: SpurMemoryManager>>ensureSemaphoreForwardedThroughContext: (in category 'interpreter access') -----
+ ensureSemaphoreForwardedThroughContext: aSemaphore
+ 	"Make sure that the aSemaphore is forwarded through to the suspendedContext of the first link."
+ 	<inline: true>
+ 	(self isForwarded: (self fetchPointer: FirstLinkIndex ofObject: aSemaphore)) ifTrue:
+ 		["0 = aSemaphore, 1 = aProcess. Hence references to suspendedContext will /not/ be forwarded."
+ 		 self followForwardedObjectFields: aSemaphore toDepth: 1].
+ 	self deny: (self isForwarded: (self
+ 									fetchPointer: SuspendedContextIndex
+ 									ofObject: (self fetchPointer: FirstLinkIndex ofObject: aSemaphore)))!

Item was changed:
  ----- Method: SpurMemoryManager>>postBecomeScanClassTable: (in category 'become implementation') -----
  postBecomeScanClassTable: effectsFlags
+ 	"Scan the class table post-become (iff an active class object was becommed) to ensure no
+ 	 forwarding pointers, and no unhashed classes exist in the class table.
+ 
- 	"Scan the class table post-become (iff a pointer object was becommed) to ensure no forwarding
- 	 pointers exist in the class table.
  	 Note that one-way become can cause duplications in the class table.
  	 When can these be eliminated?  We use the classTableBitmap to mark classTable entries
  	 (not the classes themselves, since marking a class doesn't help in knowing if its index is used).
  	 On image load, and during incrememtal scan-mark and full GC, classIndices are marked.
  	 We can somehow avoid following classes from the classTable until after this mark phase."
  	self assert: self validClassTableRootPages.
  
  	(effectsFlags anyMask: BecamePointerObjectFlag) ifFalse: [^self].
  
  	0 to: numClassTablePages - 1 do:
  		[:i| | page |
  		page := self fetchPointer: i ofObject: hiddenRootsObj.
  		self assert: (self isForwarded: page) not.
  		0 to: (self numSlotsOf: page) - 1 do:
  			[:j| | classOrNil |
  			classOrNil := self fetchPointer: j ofObject: page.
+ 			classOrNil ~= nilObj ifTrue:
+ 				[(self isForwarded: classOrNil) ifTrue:
+ 					[classOrNil := self followForwarded: classOrNil.
+ 					 self storePointer: j ofObject: page withValue: classOrNil].
+ 				 (self rawHashBitsOf: classOrNil) = 0 ifTrue:
+ 					[self storePointerUnchecked: j ofObject: page withValue: nilObj.
+ 					 "If the removed class is before the classTableIndex, set the
+ 					  classTableIndex to point to the empty slot so as to reuse it asap."
+ 					 (i << self classTableMajorIndexShift + j) < classTableIndex ifTrue:
+ 						[classTableIndex := i << self classTableMajorIndexShift + j]]]]]!
- 			(classOrNil ~= nilObj
- 			 and: [self isForwarded: classOrNil]) ifTrue:
- 				[classOrNil := self followForwarded: classOrNil.
- 				 self storePointer: j ofObject: page withValue: classOrNil]]]!

Item was changed:
  ----- Method: SpurMemoryManager>>printForwarders (in category 'debug printing') -----
  printForwarders
  	<api>
  	self allHeapEntitiesDo:
  		[:objOop|
+ 		 (self isUnambiguouslyForwarder: objOop) ifTrue:
- 		 ((self isForwarded: objOop) and: [(self isFreeObject: objOop) not]) ifTrue:
  			[coInterpreter printHex: objOop; cr]]!

Item was changed:
  ----- Method: SpurMemoryManager>>storeImageSegmentInto:outPointers:roots: (in category 'image segment in/out') -----
  storeImageSegmentInto: segmentWordArray outPointers: outPointerArray roots: arrayOfRoots
  	"This primitive is called from Squeak as...
  		<imageSegment> storeSegmentFor: arrayOfRoots into: aWordArray outPointers: anArray."
  
  "This primitive will store a binary image segment (in the same format as the Squeak image file) of the receiver and every object in its proper tree of subParts (ie, that is not refered to from anywhere else outside the tree).  All pointers from within the tree to objects outside the tree will be copied into the array of outpointers.  In their place in the image segment will be an oop equal to the offset in the outPointer array (the first would be 4). but with the high bit set."
  
  "The primitive expects the array and wordArray to be more than adequately long.  In this case it returns normally, and truncates the two arrays to exactly the right size.  To simplify truncation, both incoming arrays are required to have large headers (i.e. be 256 words long or larger).  If either array is too small, the primitive will fail, but in no other case.
  
  During operation of the primitive, it is necessary to convert from both internal and external oops to their mapped values.  To make this fast, the original objects in question are forwarded to the mapped values.  Tables are kept of both kinds of oops.  Note that markObjects eliminates forwarding pointers, so there will be no forwarding pointers in the object graph once objects have been marked.
  
  To be specific, there are two similar tables, the outPointer array, and one in the upper eight of the segmentWordArray.  Each grows oops from the bottom up.
  
+ In case of either success or failure, the headers must be restored.  In the event of primitive failure, the table of outPointers must also be nilled out (since the garbage in the high half will not have been discarded)."
- In case of either success or failure, the headers must be restored.  In the event of primitive failure, the table of outPointers must also be nilled out (since the garbage in the high half will not have been discarded."
  
+ 	| endSeg firstIn firstOut lastIn lastOut limitSeg newSegLimit unmarkedClasses |
- 	| endSeg firstIn firstOut lastIn lastOut limitSeg newSegLimit |
  	true ifTrue: [^PrimErrUnsupported] ifFalse: [
  
  	((self hasOverflowHeader: outPointerArray)						"Must have 128-bit header"
  	and: [self hasOverflowHeader: segmentWordArray]) ifFalse:		"Must have 128-bit header"
  		[^PrimErrGenericFailure].
  
  	firstOut := outPointerArray + self baseHeaderSize.
  	lastOut := firstOut - self bytesPerOop.
  
  	limitSeg := segmentWordArray + self baseHeaderSize.
  	endSeg := segmentWordArray + (self addressAfter: segmentWordArray).
  
- 	"Write a version number for byte order and version check"
- 	limitSeg >= endSeg ifTrue: [^PrimErrGenericFailure].
- 	self longAt: limitSeg put: self imageSegmentVersion.
- 	limitSeg := limitSeg + self bytesPerOop.
- 
  	"Allocate top 1/8 of segment for table of internal oops"
  	firstIn := endSeg - ((self numSlotsOf: segmentWordArray) // 8).  "Take 1/8 of seg"
  	lastIn := firstIn - self bytesPerOop.
  
  	self assert: self allObjectsUnmarked.
  	self markObjectsIn: arrayOfRoots.
  	self markObjects.
  	self unmarkObjectsIn: arrayOfRoots.
  
+ 	"All external objects, and only they, are now marked."
+ 	unmarkedClasses := self arrayOfUnmarkedClasses.
+ 	(self isImmediate: unmarkedClasses) ifTrue:
+ 		[^PrimErrGenericFailure].
+ 
+ 	"Write a version number for byte order and version check, followed by the number of classes."
+ 	limitSeg >= endSeg ifTrue: [^PrimErrGenericFailure].
+ 	self long32At: limitSeg put: self imageSegmentVersion.
+ 	self long32At: limitSeg + 4 put: (self numSlotsOf: unmarkedClasses).
+ 	limitSeg := limitSeg + 8.
+ 
+ 	"If there are any classes then copy them into the segment, and forward their oop."
+ 	(self numSlotsOf: unmarkedClasses) > 0 ifTrue:
+ 		[((lastIn := lastIn + self bytesPerOop) >= endSeg
+ 		 or: [0 = (newSegLimit := self copyObj: arrayOfRoots toSegment: segmentWordArray addr: limitSeg stopAt: firstIn saveOopAt: lastIn)]) ifTrue:
+ 			[lastIn := lastIn - self bytesPerWord.
+ 			self restoreObjectsFrom: firstIn to: lastIn from: segmentWordArray + self baseHeaderSize to: limitSeg.
+ 			self fillObj: outPointerArray numSlots: (self numSlotsOf: outPointerArray) with: nilObj.
+ 			^PrimErrGenericFailure].
+ 		limitSeg := newSegLimit].
+ 
+ 	"Copy the array of roots into the segment, and forward its oop."
- 	"All external objects, and only they, are now marked.
- 	 Copy the array of roots into the segment, and forward its oop."
  	((lastIn := lastIn + self bytesPerOop) >= endSeg
  	 or: [0 = (newSegLimit := self copyObj: arrayOfRoots toSegment: segmentWordArray addr: limitSeg stopAt: firstIn saveOopAt: lastIn)]) ifTrue:
  		[lastIn := lastIn - self bytesPerWord.
  		self restoreObjectsFrom: firstIn to: lastIn from: segmentWordArray + self baseHeaderSize to: limitSeg.
  		self fillObj: outPointerArray numSlots: (self numSlotsOf: outPointerArray) with: nilObj.
  		^PrimErrGenericFailure].
  	limitSeg := newSegLimit.
  
  	"Now traverse arrayOfRoots, copying unmarked objects into the segment"
  
  	"Now the primitive can not fail; traverse the objects in the segment, unforwarding the originals and mapping external oops."
  	self flag: 'you are here']!

Item was changed:
  ----- Method: SpurMemoryManager>>sweepToFollowForwardersForPigCompact (in category 'compaction') -----
  sweepToFollowForwardersForPigCompact
  	"Sweep, following forwarders in all live objects.
  	 Answer the lowest forwarder in oldSpace."
  	| lowestForwarder |
  	<var: #lowestForwarder type: #usqInt>
  	self assert: (freeStart = scavenger eden start
  				  and: [scavenger futureSurvivorStart = scavenger futureSpace start]).
  	self allPastSpaceObjectsDo:
  		[:o|
  		(self isForwarded: o) ifFalse:
  			[0 to: (self numPointerSlotsOf: o) - 1 do:
  				[:i| | f |
  				f := self fetchPointer: i ofObject: o.
  				(self isOopForwarded: f) ifTrue:
  					[f := self followForwarded: f.
  					 self storePointerUnchecked: i ofObject: o withValue: f]]]].
  	lowestForwarder := 0.
  	self allOldSpaceObjectsDo:
  		[:o|
  		(self isForwarded: o)
  			ifTrue:
  				[lowestForwarder = 0 ifTrue:
+ 					[lowestForwarder := o]]
- 					[lowestForwarder := 0]]
  			ifFalse:
  				[0 to: (self numPointerSlotsOf: o) - 1 do:
  					[:i| | f |
  					f := self fetchPointer: i ofObject: o.
  					(self isOopForwarded: f) ifTrue:
  						[f := self followForwarded: f.
  						 self storePointer: i ofObject: o withValue: f]]]].
  	^lowestForwarder!

Item was changed:
  ----- Method: SpurMemoryManager>>validClassTableHashes (in category 'class table') -----
  validClassTableHashes
  	"Check the hashes of classes in the table.  The tricky thing here is that classes may be duplicated
+ 	 in the table.  So each entry must be in the table at its hash, even if it is elsewhere in the table."
- 	 in the table.  So each entry ,ust be in the table at its hash, even if it is elsewhere in the table."
  
  	self validClassTableRootPages ifFalse:
  		[^false].
  
+ 	self classTableEntriesDo:
+ 		[:classOrNil :ignored| | hash |
+ 		 (self isForwarded: classOrNil) ifTrue:
+ 			[^0].
+ 		  hash := self rawHashBitsOf: classOrNil.
+ 		  hash = 0 ifTrue:
+ 			[^false].
+ 		  (self noCheckClassAtIndex: hash) ~= classOrNil ifTrue:
+ 			[^false]].
- 	0 to: numClassTablePages - 1 do:
- 		[:i| | page |
- 		 page := self fetchPointer: i ofObject: hiddenRootsObj.
- 		 0 to: self classTablePageSize - 1 do:
- 			[:j| | classOrNil hash |
- 			classOrNil := self fetchPointer: j ofObject: page.
- 			classOrNil ~= nilObj ifTrue:
- 				[(self isForwarded: classOrNil) ifTrue:
- 					[^0].
- 				 hash := self rawHashBitsOf: classOrNil.
- 				 hash = 0 ifTrue:
- 					[^false].
- 				 (self noCheckClassAtIndex: hash) ~= classOrNil ifTrue:
- 					[^false]]]].
  
  	^true!

Item was added:
+ ----- Method: StackInterpreter>>binaryInlinePrimitive: (in category 'miscellaneous bytecodes') -----
+ binaryInlinePrimitive: primIndex
+ 	"SistaV1:	248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution."
+ 	<option: #SistaVM>
+ 	| result result64 |
+ 	primIndex caseOf: {
+ 		"2000	unchecked SmallInteger #+.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)"
+ 		[0]	->	[result := objectMemory integerObjectOf: ((objectMemory integerValueOf: (self internalStackValue: 1))
+ 															+ (objectMemory integerValueOf: self internalStackTop)).
+ 				 self internalPop: 1; internalStackTopPut: result].
+ 		"2001	unchecked SmallInteger #-.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)"
+ 		[1]	->	[result := objectMemory integerObjectOf: ((objectMemory integerValueOf: (self internalStackValue: 1))
+ 															- (objectMemory integerValueOf: self internalStackTop)).
+ 				 self internalPop: 1; internalStackTopPut: result].
+ 		"2002	unchecked SmallInteger #*.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)"
+ 		[2]	->	[result := objectMemory integerObjectOf: ((objectMemory integerValueOf: (self internalStackValue: 1))
+ 															* (objectMemory integerValueOf: self internalStackTop)).
+ 				 self internalPop: 1; internalStackTopPut: result].
+ 		"2003	unchecked SmallInteger #/.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)"
+ 		[3]	->	[result := objectMemory integerObjectOf: ((objectMemory integerValueOf: (self internalStackValue: 1))
+ 															/ (objectMemory integerValueOf: self internalStackTop)).
+ 				 self internalPop: 1; internalStackTopPut: result].
+ 		"2004	unchecked SmallInteger #//.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)"
+ 		[4]	->	[result := objectMemory integerObjectOf: ((objectMemory integerValueOf: (self internalStackValue: 1))
+ 															// (objectMemory integerValueOf: self internalStackTop)).
+ 				 self internalPop: 1; internalStackTopPut: result].
+ 		"2005	unchecked SmallInteger #\\.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)"
+ 		[5]	->	[result := objectMemory integerObjectOf: ((objectMemory integerValueOf: (self internalStackValue: 1))
+ 															\\ (objectMemory integerValueOf: self internalStackTop)).
+ 				 self internalPop: 1; internalStackTopPut: result].
+ 		"2006	unchecked SmallInteger #quo:.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)"
+ 		[6]	->	[| rcvr arg |
+ 				 rcvr := objectMemory integerValueOf: (self internalStackValue: 1).
+ 				 arg := objectMemory integerValueOf: self internalStackTop.
+ 				 result := self quot: rcvr ient: arg.
+ 				 self internalPop: 1; internalStackTopPut: (objectMemory integerObjectOf: result)].
+ 
+ 		"2016	unchecked SmallInteger #bitAnd:.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)"
+ 		[16]	->	[result := objectMemory integerObjectOf: ((objectMemory integerValueOf: (self internalStackValue: 1))
+ 															bitAnd: (objectMemory integerValueOf: self internalStackTop)).
+ 					 self internalPop: 1; internalStackTopPut: result].
+ 		"2017	unchecked SmallInteger #bitOr:.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)"
+ 		[17]	->	[result := objectMemory integerObjectOf: ((objectMemory integerValueOf: (self internalStackValue: 1))
+ 															bitOr: (objectMemory integerValueOf: self internalStackTop)).
+ 					 self internalPop: 1; internalStackTopPut: result].
+ 		"2018	unchecked SmallInteger #bitXor:.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)"
+ 		[18]	->	[result := objectMemory integerObjectOf: ((objectMemory integerValueOf: (self internalStackValue: 1))
+ 															bitXor: (objectMemory integerValueOf: self internalStackTop)).
+ 					 self internalPop: 1; internalStackTopPut: result].
+ 		"2019	unchecked SmallInteger #bitShift:.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)"
+ 		[19]	->	[result := objectMemory integerObjectOf: ((objectMemory integerValueOf: (self internalStackValue: 1))
+ 															bitShift: (objectMemory integerValueOf: self internalStackTop)).
+ 					 self internalPop: 1; internalStackTopPut: result].
+ 
+ 		"2032	unchecked SmallInteger #>.  Both arguments are SmallIntegers"
+ 		[32]	->	[result := objectMemory booleanObjectOf: ((self internalStackValue: 1) > self internalStackTop).
+ 					 self internalPop: 1; internalStackTopPut: result].
+ 		"2033	unchecked SmallInteger #<.  Both arguments are SmallIntegers"
+ 		[33]	->	[result := objectMemory booleanObjectOf: ((self internalStackValue: 1) < self internalStackTop).
+ 					 self internalPop: 1; internalStackTopPut: result].
+ 		"2034	unchecked SmallInteger #>=.  Both arguments are SmallIntegers"
+ 		[34]	->	[result := objectMemory booleanObjectOf: ((self internalStackValue: 1) >= self internalStackTop).
+ 					 self internalPop: 1; internalStackTopPut: result].
+ 		"2035	unchecked SmallInteger #<=.  Both arguments are SmallIntegers"
+ 		[35]	->	[result := objectMemory booleanObjectOf: ((self internalStackValue: 1) <= self internalStackTop).
+ 					 self internalPop: 1; internalStackTopPut: result].
+ 		"2036	unchecked SmallInteger #=.  Both arguments are SmallIntegers"
+ 		[36]	->	[result := objectMemory booleanObjectOf: ((self internalStackValue: 1) = self internalStackTop).
+ 					 self internalPop: 1; internalStackTopPut: result].
+ 		"2037	unchecked SmallInteger #~=.  Both arguments are SmallIntegers"
+ 		[37]	->	[result := objectMemory booleanObjectOf: ((self internalStackValue: 1) ~= self internalStackTop).
+ 					 self internalPop: 1; internalStackTopPut: result].
+ 
+ 		"2064	unchecked Pointer Object>>at:.		The receiver is guaranteed to be a pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger"
+ 		[64]	->	[result := objectMemory
+ 									fetchPointer: (objectMemory integerValueOf: self internalStackTop)
+ 									ofObject: (self internalStackValue: 1).
+ 					 self internalPop: 1; internalStackTopPut: result].
+ 		"2065	unchecked Byte Object>>at:.			The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The result is a SmallInteger."
+ 		[65]	->	[result := objectMemory
+ 									fetchByte: (objectMemory integerValueOf: self internalStackTop)
+ 									ofObject: (self internalStackValue: 1).
+ 					 self internalPop: 1; internalStackTopPut: (objectMemory integerObjectOf: result)].
+ 		"2066	unchecked 16-bit Word Object>>at:.			The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The result is a SmallInteger."
+ 		[66]	->	[result := objectMemory
+ 									fetchShort16: (objectMemory integerValueOf: self internalStackTop)
+ 									ofObject: (self internalStackValue: 1).
+ 					 self internalPop: 1; internalStackTopPut: (objectMemory integerObjectOf: result)].
+ 		"2067	unchecked 32 bit Word Object>>at:.	The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The result is a SmallInteger or a LargePositiveInteger."
+ 		[67]	->	[result := objectMemory
+ 									fetchLong32: (objectMemory integerValueOf: self internalStackTop)
+ 									ofObject: (self internalStackValue: 1).
+ 					 self internalPop: 1; internalStackTopPut: (self signed64BitValueOf: result)].
+ 		"2068	unchecked 64 bit Word Object>>at:.		The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The result is a SmallInteger or a LargePositiveInteger."
+ 		[68]	->	[result64 := objectMemory
+ 									fetchLong64: (objectMemory integerValueOf: self internalStackTop)
+ 									ofObject: (self internalStackValue: 1).
+ 					 self internalPop: 1; internalStackTopPut: (self signed64BitValueOf: result)] }
+ 	otherwise:
+ 		[localIP := localIP - 3.
+ 		 self respondToUnknownBytecode]!

Item was changed:
  ----- Method: StackInterpreter>>callPrimitiveBytecode (in category 'miscellaneous bytecodes') -----
  callPrimitiveBytecode
  	"V4:			249		11111001	i i i i i i i i	jjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjjj * 256)
  	 SistaV1:	248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution."
  	self cppIf: SistaVM
  		ifTrue:
+ 			[| byte1 byte2 prim |
- 			[| byte1 byte2 |
  			 byte1 := self fetchByte.
  			 byte2 := self fetchByte.
  			 self fetchNextBytecode.
+ 			 byte2 < 128 ifTrue:
+ 				[localIP := localIP - 3.
+ 				 ^self respondToUnknownBytecode].
+ 			 prim := byte2 - 128 << 8 + byte1.
+ 			 prim < 1000 ifTrue:
+ 				[^self nullaryInlinePrimitive: prim].
+ 
+ 			 prim < 2000 ifTrue:
+ 				[^self unaryInlinePrimitive: prim - 1000].
+ 				
+ 			 prim < 3000 ifTrue:
+ 				[^self binaryInlinePrimitive: prim - 2000].
+ 
+ 			 prim < 4000 ifTrue:
+ 				[^self trinaryInlinePrimitive: prim - 3000].
+ 
+ 			 localIP := localIP - 3.
+ 			 ^self respondToUnknownBytecode]
- 			 byte2 > 127
- 				ifTrue:
- 					[self inlinePrimitiveBytecode: (byte2 bitAnd: 16r7F) << 8 + byte1]
- 				ifFalse:
- 					[self error: 'non-inlined callPrimitiveBytecode should not be evaluated. method activation should step beyond this bytecode.']]
  		ifFalse:
  			[self error: 'callPrimitiveBytecode should not be evaluated. method activation should step beyond this bytecode.']
  
  	"We could make it a noop and not skip it in {foo}ActivateMethod, as in:
  
  	localIP := localIP + 3.
  	self fetchNextBytecode
  
  	 But for now, having {foo}ActivateMethod skip it makes it available for invoking embedded primitives."!

Item was changed:
  ----- Method: StackInterpreter>>extTrapIfNotInstanceOfBehaviorsBytecode (in category 'sista bytecodes') -----
  extTrapIfNotInstanceOfBehaviorsBytecode
  	"SistaV1: *	236	11101100	iiiiiiii	Trap If Not Instance Of Behavior/Array Of Behavior #iiiiiiii (+ Extend A * 256, where Extend A >= 0)"
  	| tos tosClassTag literal |
  	tos := self internalStackTop.
  	tosClassTag := objectMemory fetchClassTagOf: tos.
  	literal := self literal: extA << 8 + self fetchByte.
  	extA := 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:
+ 				[^self respondToSistaTrap]]
- 				[^self respondToClassTrap]]
  		ifFalse:
  			[tosClassTag ~= (objectMemory rawClassTagForClass: literal) ifTrue:
+ 				[^self respondToSistaTrap]].
- 				[^self respondToClassTrap]].
  	self internalPopStack.
  	self fetchNextBytecode!

Item was added:
+ ----- Method: StackInterpreter>>nullaryInlinePrimitive: (in category 'miscellaneous bytecodes') -----
+ nullaryInlinePrimitive: primIndex
+ 	"SistaV1:	248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution."
+ 	<option: #SistaVM>
+ 	localIP := localIP - 3.
+ 	self respondToUnknownBytecode!

Item was removed:
- ----- Method: StackInterpreter>>respondToClassTrap (in category 'sista bytecodes') -----
- respondToClassTrap
- 	| ourContext tos |
- 	<sharedCodeInCase: #extTrapIfNotInstanceOfBehaviorsBytecode>
- 	messageSelector := objectMemory splObj: SelectorClassTrap.
- 	tos := self internalPopStack.
- 	ourContext := self ensureFrameIsMarried: localFP SP: localSP.
- 	messageSelector = objectMemory nilObject ifTrue:
- 		[self error: 'class trap'].
- 	self internalPush: ourContext.
- 	self internalPush: tos.
- 	argumentCount := 1.
- 	self normalSend!

Item was added:
+ ----- Method: StackInterpreter>>respondToSistaTrap (in category 'sista bytecodes') -----
+ respondToSistaTrap
+ 	| ourContext tos |
+ 	<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: StackInterpreter>>synchronousSignal: (in category 'process primitive support') -----
  synchronousSignal: aSemaphore 
  	"Signal the given semaphore from within the interpreter.
  	 Answer if the current process was preempted."
  	| excessSignals |
  	<inline: false>
  	(self isEmptyList: aSemaphore) ifTrue:
  		["no process is waiting on this semaphore"
  		 excessSignals := self fetchInteger: ExcessSignalsIndex ofObject: aSemaphore.
  		 self storeInteger: ExcessSignalsIndex
  			ofObject: aSemaphore
  			withValue: excessSignals + 1.
  		 ^false].
  
+ 	objectMemory ensureSemaphoreForwardedThroughContext: aSemaphore.
- 	objectMemory hasSpurMemoryManagerAPI ifTrue:
- 		[| firstLink |
- 		 firstLink := objectMemory fetchPointer: FirstLinkIndex ofObject: aSemaphore.
- 		 (objectMemory isForwarded: firstLink) ifTrue:
- 			["0 = aSemaphore, 1 = aProcess. Hence reference to suspendedContext will /not/ be forwarded."
- 			 objectMemory followForwardedObjectFields: aSemaphore toDepth: 1].
- 		 self assert: (objectMemory isForwarded: (objectMemory fetchPointer: SuspendedContextIndex ofObject: firstLink)) not].
  
  	^self resume: (self removeFirstLinkOfList: aSemaphore)
  		preemptedYieldingIf: preemptionYields!

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

Item was added:
+ ----- Method: StackInterpreter>>unaryInlinePrimitive: (in category 'miscellaneous bytecodes') -----
+ unaryInlinePrimitive: primIndex
+ 	"SistaV1:	248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution."
+ 	<option: #SistaVM>
+ 	| result |
+ 	primIndex caseOf: {
+ 		"1000	unchecked class"
+ 		[0]	->	[result := objectMemory fetchClassOf: self internalStackTop.
+ 				 self internalStackTopPut: result].
+ 		"1001	unchecked pointer numSlots"
+ 		[1]	->	[result := objectMemory numSlotsOf: self internalStackTop.
+ 				 self internalStackTopPut: (objectMemory integerObjectOf: result)].
+ 		"1002	unchecked pointer basicSize"
+ 		[2]	->	[result := (objectMemory numSlotsOf: self internalStackTop)
+ 						- (objectMemory fixedFieldsOfClass: (objectMemory fetchClassOfNonImm: self internalStackTop)).
+ 				 self internalStackTopPut: (objectMemory integerObjectOf: result)].
+ 		"1003	unchecked byte8Type format numBytes (includes CompiledMethod)"
+ 		[3]	->	[result := objectMemory numBytesOf: self internalStackTop.
+ 				 self internalStackTopPut: (objectMemory integerObjectOf: result)].
+ 		"1004	unchecked short16Type format numShorts"
+ 		[4]	->	[result := objectMemory num16BitUnitsOf: self internalStackTop.
+ 				 self internalStackTopPut: (objectMemory integerObjectOf: result)].
+ 		"1005	unchecked word32Type format numWords"
+ 		[5]	->	[result := objectMemory num32BitUnitsOf: self internalStackTop.
+ 				 self internalStackTopPut: (objectMemory integerObjectOf: result)].
+ 		"1006	unchecked doubleWord64Type format numDoubleWords"
+ 		[6]	->	[result := objectMemory num64BitUnitsOf: self internalStackTop.
+ 				 self internalStackTopPut: (objectMemory integerObjectOf: result)] }
+ 	otherwise:
+ 		[localIP := localIP - 3.
+ 		 self respondToUnknownBytecode]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>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:"
- 	 See EncoderForSistaV1's class comment and StackInterpreter>>#inlinePrimitiveBytecode:"
  	| ra val untaggedVal |
  	(ra := backEnd availableRegisterOrNilFor: self liveRegisters) ifNil:
  		[self ssAllocateRequiredReg:
  			(ra := optStatus isReceiverResultRegLive
  					ifTrue: [Arg0Reg]
  					ifFalse: [ReceiverResultReg])].
  	ra = ReceiverResultReg ifTrue:
  		[optStatus isReceiverResultRegLive: false].
  	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 SubCq: untaggedVal R: ra].
  		[2]	->	[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: ra.
  				 self MoveCq: (objectMemory integerValueOf: val) R: TempReg.
  				 self MulR: TempReg R: ra.
  				 objectRepresentation genAddSmallIntegerTagsTo: ra].
  
+ 		"2016 through 2019, bitAnd:, bitOr:, bitXor, bitShift:, SmallInteger op SmallInteger => SmallInteger, no overflow"
- 		"16 through 19, bitAnd:, bitOr:, bitXor, bitShift:, SmallInteger op SmallInteger => SmallInteger, no overflow"
  
+ 		"2032	through 2037, >, <, >=, <=. =, ~=, SmallInteger op SmallInteger => Boolean (flags?? then in jump bytecodes if ssTop is a flags value, just generate the instruction!!!!)"
- 		"32	through 37, >, <, >=, <=. =, ~=, SmallInteger op SmallInteger => Boolean (flags?? then in jump bytecodes if ssTop is a flags value, just generate the instruction!!!!)"
  
+ 		"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	through 68, Pointer Object>>at:, Byte Object>>at:, Short16 Word Object>>at: LongWord32 Object>>at: Quad64Word Object>>at:. obj op 0-rel SmallInteger => oop"
  
- 		"80	through 84, Pointer Object>>at:put:, Byte Object>>at:put:, Short16 Word Object>>at:put: LongWord32 Object>>at:put: Quad64Word Object>>at:put:. obj op 0-rel SmallInteger => oop"
- 
  	}
  	otherwise: [^EncounteredUnknownBytecode].
  	self ssPushRegister: ra.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genBinaryVarOpConstInlinePrimitive: (in category 'inline primitive generators') -----
  genBinaryVarOpConstInlinePrimitive: prim
  	"Var op const version of inline 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:"
- 	 See EncoderForSistaV1's class comment and StackInterpreter>>#inlinePrimitiveBytecode:"
  	| rr val untaggedVal |
  	(rr := backEnd availableRegisterOrNilFor: self liveRegisters) ifNil:
  		[self ssAllocateRequiredReg:
  			(rr := optStatus isReceiverResultRegLive
  					ifTrue: [Arg0Reg]
  					ifFalse: [ReceiverResultReg])].
  	rr = ReceiverResultReg ifTrue:
  		[optStatus isReceiverResultRegLive: false].
  	val := self ssTop constant.
  	self ssPop: 1.
  	self ssTop popToReg: rr.
  	self ssPop: 1.
  	untaggedVal := val - objectMemory smallIntegerTag.
  	prim caseOf: {
  		"0 through 6, +, -, *, /, //, \\, quo:, SmallInteger op SmallInteger => SmallInteger, no overflow"
  		[0]	->	[self AddCq: untaggedVal R: rr].
  		[1]	->	[self SubCq: untaggedVal R: rr].
  		[2]	->	[self flag: 'could use MulCq:R'.
  				 objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: rr.
  				 self MoveCq: (objectMemory integerValueOf: val) R: TempReg.
  				 self MulR: TempReg R: rr.
  				 objectRepresentation genAddSmallIntegerTagsTo: rr].
  
+ 		"2016 through 2019, bitAnd:, bitOr:, bitXor, bitShift:, SmallInteger op SmallInteger => SmallInteger, no overflow"
- 		"16 through 19, bitAnd:, bitOr:, bitXor, bitShift:, SmallInteger op SmallInteger => SmallInteger, no overflow"
  
+ 		"2032	through 2037, >, <, >=, <=. =, ~=, SmallInteger op SmallInteger => Boolean (flags?? then in jump bytecodes if ssTop is a flags value, just generate the instruction!!!!)"
- 		"32	through 37, >, <, >=, <=. =, ~=, SmallInteger op SmallInteger => Boolean (flags?? then in jump bytecodes if ssTop is a flags value, just generate the instruction!!!!)"
  
+ 		"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	through 68, Pointer Object>>at:, Byte Object>>at:, Short16 Word Object>>at: LongWord32 Object>>at: Quad64Word Object>>at:. obj op 0-rel SmallInteger => oop"
  
- 		"80	through 84, Pointer Object>>at:put:, Byte Object>>at:put:, Short16 Word Object>>at:put: LongWord32 Object>>at:put: Quad64Word Object>>at:put:. obj op 0-rel SmallInteger => oop"
- 
  	}
  	otherwise: [^EncounteredUnknownBytecode].
  	self ssPushRegister: rr.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genBinaryVarOpVarInlinePrimitive: (in category 'inline primitive generators') -----
  genBinaryVarOpVarInlinePrimitive: prim
  	"Var 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:"
- 	 See EncoderForSistaV1's class comment and StackInterpreter>>#inlinePrimitiveBytecode:"
  	| ra rr |
  	(rr := backEnd availableRegisterOrNilFor: self liveRegisters) ifNil:
  		[self ssAllocateRequiredReg:
  			(rr := optStatus isReceiverResultRegLive
  					ifTrue: [Arg0Reg]
  					ifFalse: [ReceiverResultReg])].
  	(ra := backEnd availableRegisterOrNilFor: (self liveRegisters bitOr: (self registerMaskFor: rr))) ifNil:
  		[self ssAllocateRequiredReg: (ra := Arg1Reg)].
  	(rr = ReceiverResultReg or: [ra = ReceiverResultReg]) ifTrue:
  		[optStatus isReceiverResultRegLive: false].
  	self ssTop popToReg: ra.
  	self ssPop: 1.
  	self ssTop popToReg: rr.
  	self ssPop: 1.
  	prim caseOf: {
  		"0 through 6, +, -, *, /, //, \\, quo:, SmallInteger op SmallInteger => SmallInteger, no overflow"
  		[0]	->	[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: ra.
  				 self AddR: ra R: rr].
  		[1]	->	[self SubR: ra R: rr.
  				 objectRepresentation genAddSmallIntegerTagsTo: rr].
  		[2]	->	[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: rr.
  				 objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: ra.
  				 self MulR: ra R: rr.
  				 objectRepresentation genAddSmallIntegerTagsTo: rr].
  
+ 		"2016 through 2019, bitAnd:, bitOr:, bitXor, bitShift:, SmallInteger op SmallInteger => SmallInteger, no overflow"
- 		"16 through 19, bitAnd:, bitOr:, bitXor, bitShift:, SmallInteger op SmallInteger => SmallInteger, no overflow"
  
+ 		"2032	through 2037, >, <, >=, <=. =, ~=, SmallInteger op SmallInteger => Boolean (flags?? then in jump bytecodes if ssTop is a flags value, just generate the instruction!!!!)"
- 		"32	through 37, >, <, >=, <=. =, ~=, SmallInteger op SmallInteger => Boolean (flags?? then in jump bytecodes if ssTop is a flags value, just generate the instruction!!!!)"
  
+ 		"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	through 68, Pointer Object>>at:, Byte Object>>at:, Short16 Word Object>>at: LongWord32 Object>>at: Quad64Word Object>>at:. obj op 0-rel SmallInteger => oop"
  
- 		"80	through 84, Pointer Object>>at:put:, Byte Object>>at:put:, Short16 Word Object>>at:put: LongWord32 Object>>at:put: Quad64Word Object>>at:put:. obj op 0-rel SmallInteger => oop"
- 
  	}
  	otherwise: [^EncounteredUnknownBytecode].
  	self ssPushRegister: rr.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genNullaryInlinePrimitive: (in category 'inline primitive generators') -----
  genNullaryInlinePrimitive: prim
  	"Nullary 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>>#nullaryInlinePrimitive:"
- 	 See EncoderForSistaV1's class comment and StackInterpreter>>#inlinePrimitiveBytecode:"
  
  	^EncounteredUnknownBytecode!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genTrinaryInlinePrimitive: (in category 'inline primitive generators') -----
  genTrinaryInlinePrimitive: prim
  	"Unary 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>>#trinaryInlinePrimitive:"
- 	 See EncoderForSistaV1's class comment and StackInterpreter>>#inlinePrimitiveBytecode:"
  	"not yet implemented"
  	^EncounteredUnknownBytecode!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genUnaryInlinePrimitive: (in category 'inline primitive generators') -----
  genUnaryInlinePrimitive: prim
  	"Unary 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>>#unaryInlinePrimitive:"
- 	 See EncoderForSistaV1's class comment and StackInterpreter>>#inlinePrimitiveBytecode:"
  	| rcvrReg resultReg |
  	self ssTop type = SSRegister
  		ifTrue: [rcvrReg := self ssTop register]
  		ifFalse:
  			[(rcvrReg := backEnd availableRegisterOrNilFor: self liveRegisters) ifNil:
  				[self ssAllocateRequiredReg:
  					(rcvrReg := optStatus isReceiverResultRegLive
  							ifTrue: [Arg0Reg]
  							ifFalse: [ReceiverResultReg])]].
  	self ssTop popToReg: rcvrReg.
  	self ssPop: 1.
  	(resultReg := backEnd availableRegisterOrNilFor: self liveRegisters) ifNil:
  		[self ssFlushUpThroughRegister: rcvrReg].
  	prim
  		caseOf: {
  			[1] ->	"01		unchecked pointer numSlots"
  				[resultReg ifNil: [resultReg := rcvrReg].
  				 objectRepresentation
  					genGetNumSlotsOf: rcvrReg into: resultReg;
  					genConvertIntegerToSmallIntegerInScratchReg: resultReg.
  				 self ssPushRegister: resultReg].
  				  }
  		otherwise:
  			[^EncounteredUnknownBytecode].
  	^0!

Item was changed:
  SharedPool subclass: #VMObjectIndices
  	instanceVariableNames: ''
+ 	classVariableNames: 'ActiveProcessIndex CharacterTable CharacterValueIndex ClassAlien ClassArray ClassBitmap ClassBlockClosure ClassBlockContext ClassByteArray ClassByteString ClassCharacter ClassExternalAddress ClassExternalData ClassExternalFunction ClassExternalLibrary ClassExternalStructure ClassFloat ClassLargeNegativeInteger ClassLargePositiveInteger ClassMessage ClassMethodContext ClassMutex ClassPoint ClassSemaphore ClassSmallInteger ClassString ClassUnsafeAlien ClassWeakFinalizer ClosureCopiedValuesIndex ClosureFirstCopiedValueIndex ClosureIndex ClosureNumArgsIndex ClosureOuterContextIndex ClosureStartPCIndex CompactClasses ConstMinusOne ConstOne ConstTwo ConstZero ExcessSignalsIndex ExternalObjectsArray FalseObject FirstLinkIndex ForeignCallbackProcess HeaderIndex InstanceSpecificationIndex InstructionPointerIndex KeyIndex LastLinkIndex LiteralStart MessageArgumentsIndex MessageLookupClassIndex MessageSelectorIndex MethodArrayIndex MethodDictionaryIndex MethodIndex MyListIndex NextLinkIndex NilObject PrimErrTableIndex PriorityIndex ProcessInExternalCodeTag ProcessListsIndex ProcessSignalingLowSpace ReceiverIndex SchedulerAssociation SelectorAboutToReturn SelectorAttemptToAssign SelectorCannotInterpret SelectorCannotReturn SelectorCounterTripped SelectorDoesNotUnderstand SelectorInvokeCallback SelectorMustBeBoolean SelectorRunWithIn SelectorSistaTrap SelectorStart SelectorUnknownBytecode SenderIndex SpecialSelectors StackPointerIndex StreamArrayIndex StreamIndexIndex StreamReadLimitIndex StreamWriteLimitIndex SuperclassIndex SuspendedContextIndex TheDisplay TheFinalizationSemaphore TheInputSemaphore TheInterruptSemaphore TheLowSpaceSemaphore TheTimerSemaphore TrueObject ValueIndex XIndex YIndex'
- 	classVariableNames: 'ActiveProcessIndex CharacterTable CharacterValueIndex ClassAlien ClassArray ClassBitmap ClassBlockClosure ClassBlockContext ClassByteArray ClassByteString ClassCharacter ClassExternalAddress ClassExternalData ClassExternalFunction ClassExternalLibrary ClassExternalStructure ClassFloat ClassLargeNegativeInteger ClassLargePositiveInteger ClassMessage ClassMethodContext ClassMutex ClassPoint ClassSemaphore ClassSmallInteger ClassString ClassUnsafeAlien ClassWeakFinalizer ClosureCopiedValuesIndex ClosureFirstCopiedValueIndex ClosureIndex ClosureNumArgsIndex ClosureOuterContextIndex ClosureStartPCIndex CompactClasses ConstMinusOne ConstOne ConstTwo ConstZero ExcessSignalsIndex ExternalObjectsArray FalseObject FirstLinkIndex ForeignCallbackProcess HeaderIndex InstanceSpecificationIndex InstructionPointerIndex KeyIndex LastLinkIndex LiteralStart MessageArgumentsIndex MessageLookupClassIndex MessageSelectorIndex MethodArrayIndex MethodDictionaryIndex MethodIndex MyListIndex NextLinkIndex NilObject PrimErrTableIndex PriorityIndex ProcessInExternalCodeTag ProcessListsIndex ProcessSignalingLowSpace ReceiverIndex SchedulerAssociation SelectorAboutToReturn SelectorAttemptToAssign SelectorCannotInterpret SelectorCannotReturn SelectorClassTrap SelectorCounterTripped SelectorDoesNotUnderstand SelectorInvokeCallback SelectorMustBeBoolean SelectorRunWithIn SelectorStart SelectorUnknownBytecode SenderIndex SpecialSelectors StackPointerIndex StreamArrayIndex StreamIndexIndex StreamReadLimitIndex StreamWriteLimitIndex SuperclassIndex SuspendedContextIndex TheDisplay TheFinalizationSemaphore TheInputSemaphore TheInterruptSemaphore TheLowSpaceSemaphore TheTimerSemaphore TrueObject ValueIndex XIndex YIndex'
  	poolDictionaries: ''
  	category: 'VMMaker-Interpreter'!
  
  !VMObjectIndices commentStamp: '<historical>' prior: 0!
  I am a shared pool for the constants that define object layout and well-known objects shared between the object memories (e.g. ObjectMemory, NewObjectMemory), the interpreters (e.g. StackInterpreter, CoInterpreter) and the object representations (e.g. ObjectRepresentationForSqueakV3).
  
  self classPool declare: #Foo from: StackInterpreter classPool
  
  (ObjectMemory classPool keys select: [:k| (k beginsWith: 'Class') and: [(k endsWith: 'Index') not]]) do:
  	[:k| self classPool declare: k from: ObjectMemory classPool]!



More information about the Vm-dev mailing list