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

commits at source.squeak.org commits at source.squeak.org
Wed Nov 24 03:00:36 UTC 2021


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

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

Name: VMMaker.oscog-eem.3110
Author: eem
Time: 23 November 2021, 7:00:21.438658 pm
UUID: 169281c1-069d-4dbd-96cc-9cf07417c95a
Ancestors: VMMaker.oscog-eem.3109

StackInterpreter:
Implement printing suspended processes in printAllStacks by searching the heasp for all processes (including subinstances) waiting on other than a linked list.  Hence nuke ClassMutex which specifies a slot in the specialObjectsArray which has never been used in production.

CoInterpreterMT:
Override to printAllStacks also print the awol processes 

MT Simulation: fix ioWaitOnOSSemaphore: to switch regioster states correctly

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

Item was changed:
  ----- Method: CoInterpreterMT>>primitiveProcessBindToThreadId (in category 'process primitives') -----
  primitiveProcessBindToThreadId
  	"Attempt to bind the receiver to the thread with the id of the argument or nil, where the receiver is a Process.
  	 If successful the VM will ensure that there are at least id many threads active."
  	| aProcess id |
  	<export: true>
+ 	self break.
  	self cCode: [] inSmalltalk: [cogThreadManager isNil ifTrue: [^self primitiveFail]].
  	processHasThreadId ifFalse:
  		[^self primitiveFailFor: PrimErrUnsupported].
  	id := self stackTop.
  	aProcess := self stackValue: 1.
  	((id = objectMemory nilObject or: [(objectMemory isIntegerObject: id)
  										and: [id ~= (objectMemory integerObjectOf: 0)]])
  	and: [(objectMemory isPointers: aProcess)
  	and: [(objectMemory slotSizeOf: aProcess) >= (ThreadIdIndex + 1)]]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	id := id = objectMemory nilObject ifTrue: [0] ifFalse: [objectMemory integerValueOf: id].
  	id abs >= cogThreadManager maxNumThreads ifTrue:
  		[^self primitiveFailFor: PrimErrLimitExceeded].
  	(self bindProcess: aProcess toId: id) ifNotNil:
  		[:ec| ^self primitiveFailFor: ec].
  	id := self ownerIndexOfProcess: aProcess.
  	(aProcess = self activeProcess
  	and: [(activeProcessAffined := id ~= 0)
  	and: [(cogThreadManager vmOwnerIsCompatibleWith: id) not]]) ifTrue:
  		[(self quickFetchInteger: PriorityIndex ofObject: aProcess) < maxWaitingPriority ifTrue:
  			[maxWaitingPriority = self quickFetchInteger: PriorityIndex ofObject: aProcess].
  		 checkThreadActivation := true.
  		 self forceInterruptCheck].
  	self methodReturnReceiver!

Item was added:
+ ----- Method: CoInterpreterMT>>printAllStacks (in category 'debug printing') -----
+ printAllStacks
+ 	"Print all the stacks of all running processes, including those that are currently suspended.
+ 	 Override to print the AWOL processes."
+ 	super printAllStacks.
+ 	self cr; print: 'awol processes'.
+ 	1 to: cogThreadManager getNumThreads do:
+ 		[:i| | vmThread |
+ 		vmThread := cogThreadManager vmThreadAt: i.
+ 		vmThread state ifNotNil:
+ 			[vmThread awolProcIndex > 0 ifTrue:
+ 				[self cr; print: 'thread '; printNum: i.
+ 				 0 to: vmThread awolProcIndex - 1 do:
+ 					[:j|
+ 					self printProcessStack: (vmThread awolProcesses at: j)]]]]!

Item was changed:
  ----- Method: CogThreadManager>>ioWaitOnOSSemaphore: (in category 'simulation') -----
  ioWaitOnOSSemaphore: aSemaphorePtr
  	<var: #anOSSemaphore type: #'sqOSSemaphore *'>
  	<returnTypeC: #void>
  	<doNotGenerate>
  	"See platforms/Cross/vm/sq.h for the real definition."
  	"Simulate the VM's heartbeat by calling checkVMOwnershipFromHeartbeat
  	 if the wait times-out."
+ 	| thisThread |
  	[aSemaphorePtr value waitTimeoutMSecs: 1000] whileTrue:
  		[coInterpreter checkVMOwnershipFromHeartbeat].
  	self deny: vmOwner = 0.
+ 	thisThread := self vmThreadForCurrentProcess.
  	cogit withProcessorHaltedDo:
  		[| processor |
  		processor := cogit processor.
  		registerStates
+ 			at: thisThread index
- 			at: vmOwner
  			ifPresent:
  				[:registerState|
+ 				self assertValidStackPointersInState: registerState forIndex: thisThread index].
- 				self assertValidStackPointersInState: registerState forIndex: vmOwner].
  		processor setRegisterState: (registerStates
+ 										at: thisThread index
- 										at: vmOwner
  										ifAbsentPut:
+ 											[self ensureInitializedProcessor: processor forThreadIndex: thisThread index.
- 											[self ensureInitializedProcessor: processor forThreadIndex: vmOwner.
  											 processor registerState])]!

Item was added:
+ ----- Method: CogThreadManager>>vmThreadForCurrentProcess (in category 'simulation') -----
+ vmThreadForCurrentProcess
+ 	| thisProcess |
+ 	thisProcess := Processor activeProcess.
+ 	^threads detect: [:t| t osThread = thisProcess] !

Item was added:
+ ----- Method: CogVMSimulator>>printAllStacks (in category 'multi-threading simulation switch') -----
+ printAllStacks
+ 	"This method includes or excludes CoInterpreterMT methods as required.
+ 	 Auto-generated by CogVMSimulator>>ensureMultiThreadingOverridesAreUpToDate"
+ 
+ 	^self perform: #printAllStacks
+ 		withArguments: {}
+ 		inSuperclass: (cogThreadManager ifNil: [CoInterpreterPrimitives] ifNotNil: [CoInterpreterMT])!

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.
  	ClassFullBlockClosure := 37. "Was BlockContextProto := 37."
  	ExternalObjectsArray := 38.
+ 	"ClassMutex := 39. nice idea; not used in practice..."
- 	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.
  	
  	LowcodeContextMark := 60.
  	LowcodeNativeContextClass := 61.
  !

Item was removed:
- ----- Method: ObjectMemory>>classMutex (in category 'plugin support') -----
- classMutex
- 	^self splObj: ClassMutex!

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.
  	ClassDoubleByteArray := 31.	"was the prototype Float"
  	ClassWordArray := 32.			"was the prototype 4-byte LargePositiveInteger"
  	ClassDoubleWordArray := 33.	"was the prototype Point"
  		ValidatedClassDoubleByteArrayFlag := 1.
  		ValidatedClassWordArrayFlag := 2.
  		ValidatedClassDoubleWordArrayFlag := 4.
  		ValidatedClassFloat32ArrayFlag := 8.
  		ValidatedClassFloat64ArrayFlag := 16.
  	SelectorCannotInterpret := 34.
  	"Was MethodContextProto := 35."
  	ClassBlockClosure := 36.
  	"Was BlockContextProto := 37."
  	ExternalObjectsArray := 38.
+ 	"ClassMutex := 39. nice idea; not used in practice..."
- 	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.
  	
  	LowcodeContextMark := 60.
  	LowcodeNativeContextClass := 61.!

Item was removed:
- ----- Method: SpurMemoryManager>>classMutex (in category 'plugin support') -----
- classMutex
- 	^self splObj: ClassMutex!

Item was changed:
  ----- Method: StackInterpreter>>printAllStacks (in category 'debug printing') -----
  printAllStacks
  	"Print all the stacks of all running processes, including those that are currently suspended."
  	<export: true> "useful for VM debugging; use export: not api, so it will be accessible on win32 and won't be written to cointerp.h"
+ 	| proc schedLists p processList linkedListClass minProcessInstSize processClass |
- 	| proc semaphoreClass mutexClass schedLists p processList |
  	<inline: false>
+ 	proc := self activeProcess. "may not be an instance of process. may in exceptional circumstances be nilObject"
- 	proc := self activeProcess.
  	self printNameOfClass: (objectMemory fetchClassOf: proc) count: 5; space; printHex: proc.
  	self print: ' priority '; printNum: (self quickFetchInteger: PriorityIndex ofObject: proc); cr.
+ 	framePointer
+ 		ifNil: [self printProcessStack: proc] "at startup..."
+ 		ifNotNil: [self printCallStack]. "first the current activation"
- 	self printCallStack. "first the current activation"
  	schedLists := objectMemory fetchPointer: ProcessListsIndex ofObject: self schedulerPointer.
+ 	linkedListClass := nil.
  	"then the runnable processes"
  	p := highestRunnableProcessPriority = 0
  			ifTrue: [objectMemory numSlotsOf: schedLists]
  			ifFalse: [highestRunnableProcessPriority].
  	p - 1 to: 0 by: -1 do:
  		[:pri|
  		processList := objectMemory fetchPointer: pri ofObject: schedLists.
  		(self isEmptyList: processList) ifFalse:
+ 			[proc = objectMemory nilObject ifTrue:
+ 				[proc := objectMemory fetchPointer: FirstLinkIndex ofObject: processList].
+ 			 self cr; print: 'processes at priority '; printNum: pri + 1.
+ 			 self printProcsOnList: processList].
+ 		 linkedListClass ifNil: [linkedListClass := objectMemory fetchClassOfNonImm: processList]].
+ 	linkedListClass ifNil: [linkedListClass := objectMemory superclassOf: objectMemory classSemaphore].
+ 	proc = objectMemory nilObject ifTrue:
+ 		[self cr; print: 'Cannot find a runnable process. Cannot therefore determine class Process. Cannot therefore print suspended processes'.
+ 		 ^self].
- 			[self cr; print: 'processes at priority '; printNum: pri + 1.
- 			 self printProcsOnList: processList]].
  	self cr; print: 'suspended processes'.
+ 	"Find the root of the Process hierarchy. It is the class, or superclass,
+ 	 of a process, that has inst size at least large enough to include myList"
+ 	processClass := proc = objectMemory nilObject ifFalse: [objectMemory fetchClassOf: proc].
+ 	minProcessInstSize := MyListIndex + 1.
+ 	[(objectMemory instanceSizeOf: (objectMemory superclassOf: processClass)) >= minProcessInstSize] whileTrue:
+ 		[processClass := objectMemory superclassOf: processClass].
+ 	minProcessInstSize := objectMemory instanceSizeOf: processClass.
+ 	"look for all subInstances of process that have a context as a suspendedContext and are on a list other than a LinkedList"
- 	semaphoreClass := objectMemory classSemaphore.
- 	mutexClass := objectMemory classMutex.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
+ 			[objectMemory allHeapEntitiesDo:
+ 				[:obj|
+ 				 ((objectMemory isNormalObject: obj)
+ 				  and: [(objectMemory isPointersNonImm: obj)
+ 				  and: [(objectMemory numSlotsOf: obj) >= minProcessInstSize
+ 				  and: [(self is: obj KindOfClass: processClass)
+ 				  and: [objectMemory isContext: (objectMemory fetchPointer: SuspendedContextIndex ofObject: obj)]]]]) ifTrue:
+ 					[| myList myListClass |
+ 					"Is the process waiting on some delaying list?  This will be a subclass of LinkedList.
+ 					 If so, assume it is blocked on the list."
+ 				 	myList := objectMemory fetchPointer: MyListIndex ofObject: obj.
+ 					(myList ~= objectMemory nilObject
+ 					 and: [(myListClass := objectMemory fetchClassOfNonImm: myList) ~= linkedListClass
+ 					 and: [self is: myList KindOfClass: linkedListClass]]) ifTrue:
+ 						[self printProcessStack: obj]]]]
- 			[semaphoreClass := objectMemory compactIndexOfClass: semaphoreClass.
- 			 mutexClass := objectMemory compactIndexOfClass: mutexClass.
- 			 objectMemory allHeapEntitiesDo:
- 				[:obj| | classIdx |
- 				 classIdx := objectMemory classIndexOf: obj.
- 				 (classIdx = semaphoreClass
- 				  or: [classIdx = mutexClass]) ifTrue:
- 					[self printProcsOnList: obj]]]
  		ifFalse:
  			[objectMemory allObjectsDoSafely:
+ 				[:obj|
+ 				 ((objectMemory isNormalObject: obj)
+ 				  and: [(objectMemory isPointersNonImm: obj)
+ 				  and: [(objectMemory numSlotsOf: obj) >= minProcessInstSize
+ 				  and: [(self is: obj KindOfClass: processClass)
+ 				  and: [objectMemory isContext: (objectMemory fetchPointer: SuspendedContextIndex ofObject: obj)]]]]) ifTrue:
+ 					[| myList myListClass |
+ 					"Is the process waiting on some delaying list?  This will be a subclass of LinkedList.
+ 					 If so, assume it is blocked on the list."
+ 				 	myList := objectMemory fetchPointer: MyListIndex ofObject: obj.
+ 					(myList ~= objectMemory nilObject
+ 					 and: [(myListClass := objectMemory fetchClassOfNonImm: myList) ~= linkedListClass
+ 					 and: [self is: myList KindOfClass: linkedListClass]]) ifTrue:
+ 						[self printProcessStack: obj]]]]!
- 				[:obj| | classObj |
- 				 classObj := objectMemory fetchClassOfNonImm: obj.
- 				 (classObj = semaphoreClass
- 				  or: [classObj = mutexClass]) ifTrue:
- 					[self printProcsOnList: obj]]]!

Item was changed:
  ----- Method: StackInterpreter>>printCallStack (in category 'debug printing') -----
  printCallStack
  	<export: true> "useful for VM debugging; use export: not api, so it will be accessible on win32 and won't be written to cointerp.h"
  	<inline: false>
+ 	framePointer
+ 		ifNil: [self printCallStackOf: (objectMemory fetchPointer: SuspendedContextIndex ofObject: self activeProcess)]
+ 		ifNotNil: [self printCallStackFP: framePointer]!
- 	framePointer = nil
- 		ifTrue: [self printCallStackOf: (objectMemory fetchPointer: SuspendedContextIndex ofObject: self activeProcess)]
- 		ifFalse: [self printCallStackFP: framePointer]!

Item was changed:
  ----- Method: StackInterpreter>>printCallStackFP: (in category 'debug printing') -----
  printCallStackFP: theFP
+ 	<var: #theFP type: #'char *'>
  	| context |
  	<inline: false>
+ 	self cCode: '' inSmalltalk: [transcript ensureCr].
- 	<var: #theFP type: #'char *'>
  	context := self shortReversePrintFrameAndCallers: theFP.
  	[context = objectMemory nilObject] whileFalse:
  		[(self isMarriedOrWidowedContext: context)
  			ifTrue:
  				[(self checkIsStillMarriedContext: context currentFP: framePointer) ifFalse:
  					[self shortPrintContext: context.
  					 ^nil].
  				 context := self shortReversePrintFrameAndCallers: (self frameOfMarriedContext: context)]
  			ifFalse:
  				[context := self printContextCallStackOf: context]]!

Item was changed:
  ----- Method: StackInterpreter>>printCallStackOf: (in category 'debug printing') -----
  printCallStackOf: aContextOrProcessOrFrame
  	<export: true> "useful for VM debugging; use export: not api, so it will be accessible on win32 and won't be written to cointerp.h"
  	| context |
  	<inline: false>
+ 	self cCode: '' inSmalltalk: [transcript ensureCr].
  	(stackPages couldBeFramePointer: aContextOrProcessOrFrame) ifTrue:
  		[^self printCallStackFP: (self cCoerceSimple: aContextOrProcessOrFrame to: #'char *')].
  	aContextOrProcessOrFrame = self activeProcess ifTrue:
  		[^self printCallStackOf: self headFramePointer].
  	(self couldBeProcess: aContextOrProcessOrFrame) ifTrue:
  		[^self printCallStackOf: (objectMemory
  									fetchPointer: SuspendedContextIndex
  									ofObject: aContextOrProcessOrFrame)].
  	context := aContextOrProcessOrFrame.
  	[context = objectMemory nilObject] whileFalse:
  		[(self isMarriedOrWidowedContext: context)
  			ifTrue:
  				[(self checkIsStillMarriedContext: context currentFP: framePointer) ifFalse:
  					[self shortPrintContext: context.
  					 ^nil].
  				 context := self shortReversePrintFrameAndCallers: (self frameOfMarriedContext: context)]
  			ifFalse:
  				[context := self printContextCallStackOf: context]]!

Item was changed:
  SharedPool subclass: #VMObjectIndices
  	instanceVariableNames: ''
+ 	classVariableNames: 'ActiveProcessIndex CharacterTable CharacterValueIndex ClassAlien ClassArray ClassBitmap ClassBlockClosure ClassBlockContext ClassByteArray ClassByteString ClassCharacter ClassDoubleByteArray ClassDoubleWordArray ClassExternalAddress ClassExternalData ClassExternalFunction ClassExternalLibrary ClassExternalStructure ClassFloat ClassFullBlockClosure ClassLargeNegativeInteger ClassLargePositiveInteger ClassMessage ClassMethodContext ClassPoint ClassSemaphore ClassSmallInteger ClassString ClassUnsafeAlien ClassWeakFinalizer ClassWordArray ClosureFirstCopiedValueIndex ClosureIndex ClosureNumArgsIndex ClosureOuterContextIndex ClosureStartPCIndex CompactClasses ConstMinusOne ConstOne ConstTwo ConstZero ExcessSignalsIndex ExternalObjectsArray FalseObject FirstLinkIndex ForeignCallbackProcess FullClosureCompiledBlockIndex FullClosureFirstCopiedValueIndex FullClosureReceiverIndex HeaderIndex InstanceSpecificationIndex InstructionPointerIndex KeyIndex LastLinkIndex Liter
 alStart LowcodeContextMark LowcodeNativeContextClass 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 ClassDoubleByteArray ClassDoubleWordArray ClassExternalAddress ClassExternalData ClassExternalFunction ClassExternalLibrary ClassExternalStructure ClassFloat ClassFullBlockClosure ClassLargeNegativeInteger ClassLargePositiveInteger ClassMessage ClassMethodContext ClassMutex ClassPoint ClassSemaphore ClassSmallInteger ClassString ClassUnsafeAlien ClassWeakFinalizer ClassWordArray ClosureFirstCopiedValueIndex ClosureIndex ClosureNumArgsIndex ClosureOuterContextIndex ClosureStartPCIndex CompactClasses ConstMinusOne ConstOne ConstTwo ConstZero ExcessSignalsIndex ExternalObjectsArray FalseObject FirstLinkIndex ForeignCallbackProcess FullClosureCompiledBlockIndex FullClosureFirstCopiedValueIndex FullClosureReceiverIndex HeaderIndex InstanceSpecificationIndex InstructionPointerIndex KeyIndex LastLink
 Index LiteralStart LowcodeContextMark LowcodeNativeContextClass 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'
  	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