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

commits at source.squeak.org commits at source.squeak.org
Sat Jan 18 20:06:45 UTC 2020


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

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

Name: VMMaker.oscog-eem.2662
Author: eem
Time: 18 January 2020, 12:06:32.682741 pm
UUID: 85599973-5ac3-4251-a081-1b27cecff28e
Ancestors: VMMaker.oscog-nice.2661

Add the integer arrays to the plugin API (classDoubleByteArray et al).
Reorganize vmProxyMajor/MinorVersion so that different object memories can provide different versions (this API is only really useful in Spur).
Comment a non-obvious point with InterpreterPlugin>>setInterpreter:.

Add some optional simulation code to try and figure out the stack depth assert fails on non-local return (e.g. when simulating a Squeak trunk update we see falures in some activations of SystemProgressMorph>>nextSlotFor:).

=============== Diff against VMMaker.oscog-nice.2661 ===============

Item was changed:
  CoInterpreterMT subclass: #CogVMSimulator
  	instanceVariableNames: 'parent enableCog byteCount lastPollCount lastExtPC sendCount lookupCount printSends traceOn myBitBlt displayForm fakeForm imageName pluginList mappedPluginEntries quitBlock transcript displayView eventTransformer printFrameAtEachStep printBytecodeAtEachStep systemAttributes uniqueIndices uniqueIndex breakCount atEachStepBlock startMicroseconds lastYieldMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize debugStackDepthDictionary performFilters eventQueue expectedSends expecting'
+ 	classVariableNames: 'ByteCountsPerMicrosecond ExpectedSends NLRFailures NLRSuccesses'
- 	classVariableNames: 'ByteCountsPerMicrosecond ExpectedSends'
  	poolDictionaries: ''
  	category: 'VMMaker-JITSimulation'!
  
  !CogVMSimulator commentStamp: 'eem 9/3/2013 11:16' prior: 0!
  This class defines basic memory access and primitive simulation so that the CoInterpreter can run simulated in the Squeak environment.  It also defines a number of handy object viewing methods to facilitate pawing around in the object memory.  Remember that you can test the Cogit using its class-side in-image compilation facilities.
  
  To see the thing actually run, you could (after backing up this image and changes), execute
  
  	(CogVMSimulator new openOn: Smalltalk imageName) test
  
  and be patient both to wait for things to happen, and to accept various things that may go wrong depending on how large or unusual your image may be.  We usually do this with a small and simple benchmark image.
  
  Here's an example to launch the simulator in a window.  The bottom-right window has a menu packed with useful stuff:
  
  (CogVMSimulator newWithOptions: #(Cogit StackToRegisterMappingCogit))
  	desiredNumStackPages: 8;
  	openOn: '/Users/eliot/Cog/startreader.image';
  	openAsMorph;
  	run
  
  Here's a hairier example that I (Eliot) actually use in daily development with some of the breakpoint facilities commented out.
  
  | cos proc opts |
  CoInterpreter initializeWithOptions: (opts := Dictionary newFromPairs: #(Cogit StackToRegisterMappingCogit)).
  CogVMSimulator chooseAndInitCogitClassWithOpts: opts.
  cos := CogVMSimulator new.
  "cos initializeThreadSupport." "to test the multi-threaded VM"
  cos desiredNumStackPages: 8. "to set the size of the stack zone"
  "cos desiredCogCodeSize: 8 * 1024 * 1024." "to set the size of the Cogit's code zone"
  cos openOn: '/Users/eliot/Squeak/Squeak4.4/trunk44.image'. "choose your favourite image"
  "cos setBreakSelector: 'r:degrees:'." "set a breakpoint at a specific selector"
  proc := cos cogit processor.
  "cos cogit sendTrace: 7." "turn on tracing"
  "set a complex breakpoint at a specific point in machine code"
  "cos cogit singleStep: true; breakPC: 16r56af; breakBlock: [:cg|  cos framePointer > 16r101F3C and: [(cos longAt: cos framePointer - 4) = 16r2479A and: [(cos longAt: 16r101F30) = (cos longAt: 16r101F3C) or: [(cos longAt: 16r101F2C) = (cos longAt: 16r101F3C)]]]]; sendTrace: 1".
  "[cos cogit compilationTrace: -1] on: MessageNotUnderstood do: [:ex|]." "turn on compilation tracing in the StackToRegisterMappingCogit"
  "cos cogit setBreakMethod: 16rB38880."
  cos
  	openAsMorph;
  	"toggleTranscript;" "toggleTranscript will send output to the Transcript instead of the morph's rather small window"
  	halt;
  	run!

Item was added:
+ ----- Method: CogVMSimulator>>externalAboutToReturn:through: (in category 'return bytecodes') -----
+ externalAboutToReturn: resultOop through: aContext
+ 	| cogMethod |
+ 	cogMethod := self mframeMethod: framePointer.
+ 	"(cogMethod = 16rF0328 and:[resultOop ~= 16r3]) ifTrue: [self halt: resultOop hex]."
+ 	NLRSuccesses ifNotNil:
+ 		[NLRSuccesses at: cogMethod put: 1 + (NLRSuccesses at: cogMethod ifAbsent: 0)].
+ 	[super externalAboutToReturn: resultOop through: aContext]
+ 		on: AssertionFailure
+ 		do: [:ex|
+ 			"Block in SystemProgressMorph>>nextSlotFor:"
+ 			"cogMethod = 16rF0328 ifTrue: [self halt: resultOop hex]."
+ 			NLRSuccesses ifNotNil:
+ 				[NLRSuccesses at: cogMethod put: (NLRSuccesses at: cogMethod) - 1.
+ 				 NLRFailures at: cogMethod put: 1 + (NLRFailures at: cogMethod ifAbsent: 0)].
+ 			ex resume]
+ 
+ 	"NLRFailures := Dictionary new. NLRSuccesses := Dictionary new"
+ 	"{ NLRFailures. NLRSuccesses }"!

Item was changed:
  ----- Method: CogVMSimulator>>maybeCheckStackDepth:sp:pc: (in category 'debug support') -----
  maybeCheckStackDepth: delta sp: sp pc: mcpc
  	| asp bcpc startbcpc cogHomeMethod cogBlockMethod csp debugStackPointers |
  	debugStackDepthDictionary ifNil: [^self].
  	(self isMachineCodeFrame: framePointer) ifFalse: [^self].
  	cogBlockMethod := self mframeCogMethod: framePointer.
  	cogHomeMethod := self asCogHomeMethod: cogBlockMethod.
  	debugStackPointers := debugStackDepthDictionary
  								at: cogHomeMethod methodObject
  								ifAbsentPut: [self debugStackPointersFor: cogHomeMethod methodObject].
  	startbcpc := cogHomeMethod = cogBlockMethod
  					ifTrue: [self startPCOfMethod: cogHomeMethod methodObject]
  					ifFalse: [self startPCOfClosure: (self pushedReceiverOrClosureOfFrame: framePointer)].
  	bcpc := cogit bytecodePCFor: mcpc startBcpc: startbcpc in: cogBlockMethod.
  	self assert: bcpc ~= 0.
  	((cogBlockMethod ~= cogHomeMethod or: [cogBlockMethod cmIsFullBlock])
  	 and: [cogit isNonLocalReturnPC: mcpc]) ifTrue:
  		[| lastbcpc |
  		 "Method returns within a block (within an unwind-protect) must check the stack depth at the
  		  return, not the bytecode following, but the pc mapping maps to the bytecode following the
  		  return. lastBytecodePCForBlockAt:in: catches method returns at the end of a block, modifying
  		  the bcpc to that of the return.  isNonLocalReturnPC: catches method returns not at the end.
  		  Assumes method return bytecodes are 1 bytecode long;a  dodgy assumption, but good enough."
  		 lastbcpc := cogBlockMethod cmIsFullBlock
  						ifTrue: [cogit endPCOf: cogHomeMethod methodObject]
  						ifFalse: [cogit lastBytecodePCForBlockAt: startbcpc in: cogHomeMethod methodObject].
  		 bcpc > lastbcpc ifTrue: [bcpc := lastbcpc]].
  	asp := self stackPointerIndexForFrame: framePointer WithSP: sp + objectMemory wordSize.
  	csp := debugStackPointers at: bcpc ifAbsent: [-1].
  	"Compensate for some edge cases"
  	asp - delta = csp ifTrue:
+ 		["Compensate for the implicit context receiver push in a trap bytecode with the absence of a continuation.
- 		["Compensate for the implicit context receiver push in a trap bytecode with the absence of a contnuation.
  		  Assumes trap bytecodes are 1 byte bytecodes."
  		 (SistaVM
  		  and: [cogit isTrapAt: mcpc]) ifTrue:
  			[csp := csp + 1].
  		"Compensate lazily for absent receiver sends (cuz mapping is slow, even though incrememting csp is a dodgy idea)."
  		(NewspeakVM
  		 and: [cogit isAbsentReceiverSendAt: mcpc in: cogHomeMethod]) ifTrue:
  			[csp := debugStackPointers at: bcpc put: csp + 1]].
  	self assert: asp - delta + 1 = csp!

Item was removed:
- ----- Method: Interpreter class>>vmProxyMajorVersion (in category 'api version') -----
- vmProxyMajorVersion
- 	"Define the  VM_PROXY_MAJOR version for this VM as used to
- 	 define the api in platforms/Cross/vm/sqVirtualMachine.[ch]"
- 	^1!

Item was removed:
- ----- Method: Interpreter class>>vmProxyMinorVersion (in category 'api version') -----
- vmProxyMinorVersion
- 	"Define the  VM_PROXY_MINOR version for this VM as used to
- 	 define the api in platforms/Cross/vm/sqVirtualMachine.[ch]"
- 	^8!

Item was changed:
  ----- Method: InterpreterPlugin>>setInterpreter: (in category 'initialize') -----
  setInterpreter: anInterpreter 
  	"Note: This is coded so that it can be run in Squeak."
  
  	| ok |
  	<export: true>
  	<var: #anInterpreter type: #'struct VirtualMachine*'>
  	interpreterProxy := anInterpreter.
+ 	"This may seem tautological, but in a real plugin it checks that the VM provides
+ 	 the version the plugin was compiled against which is the version the plugin expects."
  	ok := interpreterProxy majorVersion = (self cCode: 'VM_PROXY_MAJOR' inSmalltalk: [self majorVersion])
  		and: [interpreterProxy minorVersion >= (self cCode: 'VM_PROXY_MINOR' inSmalltalk: [self minorVersion])].
  	ok ifTrue:
  		[self expandDereferenceInterpreterProxyFunctionTable].
  	^ok!

Item was added:
+ ----- Method: InterpreterProxy>>classDoubleByteArray (in category 'special classes') -----
+ classDoubleByteArray
+ 	<option: #(atLeastVMProxyMajor:minor: 1 16)>
+ 	^Smalltalk at: #DoubleByteArray ifAbsent: [nil]!

Item was added:
+ ----- Method: InterpreterProxy>>classDoubleWordArray (in category 'special classes') -----
+ classDoubleWordArray
+ 	<option: #(atLeastVMProxyMajor:minor: 1 16)>
+ 	^Smalltalk at: #DoubleWordArray ifAbsent: [nil]!

Item was added:
+ ----- Method: InterpreterProxy>>classFloat32Array (in category 'special classes') -----
+ classFloat32Array
+ 	<option: #(atLeastVMProxyMajor:minor: 1 16)>
+ 	^Smalltalk at: #FloatArray ifAbsent: [nil]!

Item was added:
+ ----- Method: InterpreterProxy>>classFloat64Array (in category 'special classes') -----
+ classFloat64Array
+ 	<option: #(atLeastVMProxyMajor:minor: 1 16)>
+ 	^Smalltalk at: #Float64Array ifAbsent: [nil]!

Item was added:
+ ----- Method: InterpreterProxy>>classWordArray (in category 'special classes') -----
+ classWordArray
+ 	<option: #(atLeastVMProxyMajor:minor: 1 16)>
+ 	^Smalltalk at: #WordArray ifAbsent: [nil]!

Item was removed:
- ----- Method: NewCoObjectMemorySimulator class>>vmProxyMajorVersion (in category 'simulation only') -----
- vmProxyMajorVersion
- 	"hack around the CoInterpreter/ObjectMemory split refactoring"
- 	^CoInterpreter vmProxyMajorVersion!

Item was removed:
- ----- Method: NewCoObjectMemorySimulator class>>vmProxyMinorVersion (in category 'simulation only') -----
- vmProxyMinorVersion
- 	"hack around the CoInterpreter/ObjectMemory split refactoring"
- 	^CoInterpreter vmProxyMinorVersion!

Item was added:
+ ----- Method: NewObjectMemory class>>vmProxyMinorVersion (in category 'api chacterization') -----
+ vmProxyMinorVersion
+ 	"Define the  VM_PROXY_MAJOR version for this VM as used to define
+ 	 the api in platforms/Cross/vm/sqVirtualMachine.[ch] and in interp.h."
+ 	^15 "isBooleanObject: & isPositiveMachineIntegerObject:"!

Item was removed:
- ----- Method: NewObjectMemorySimulator class>>vmProxyMajorVersion (in category 'simulation only') -----
- vmProxyMajorVersion
- 	"hack around the CoInterpreter/ObjectMemory split refactoring"
- 	^StackInterpreter vmProxyMajorVersion!

Item was removed:
- ----- Method: NewObjectMemorySimulator class>>vmProxyMinorVersion (in category 'simulation only') -----
- vmProxyMinorVersion
- 	"hack around the CoInterpreter/ObjectMemory split refactoring"
- 	^StackInterpreter vmProxyMinorVersion!

Item was added:
+ ----- Method: ObjectMemory class>>vmProxyMinorVersion (in category 'api chacterization') -----
+ vmProxyMinorVersion
+ 	"Define the  VM_PROXY_MAJOR version for this VM as used to define
+ 	 the api in platforms/Cross/vm/sqVirtualMachine.[ch] and in interp.h."
+ 	^8!

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.
+ 	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.
  	"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 class>>vmProxyMajorVersion (in category 'simulation only') -----
- vmProxyMajorVersion
- 	"hack around the CoInterpreter/ObjectMemory split refactoring"
- 	^StackInterpreter vmProxyMajorVersion!

Item was changed:
+ ----- Method: SpurMemoryManager class>>vmProxyMinorVersion (in category 'api characterization') -----
- ----- Method: SpurMemoryManager class>>vmProxyMinorVersion (in category 'simulation only') -----
  vmProxyMinorVersion
+ 	"Define the  VM_PROXY_MAJOR version for this VM as used to define
+ 	 the api in platforms/Cross/vm/sqVirtualMachine.[ch] and in interp.h."
+ 	^16 "classDoubleByteArray classWordArray classDoubleWordArray classFloat32Array classFloat64Array"!
- 	^StackInterpreter vmProxyMinorVersion max: 13!

Item was added:
+ ----- Method: SpurMemoryManager>>accessIntegerClass:withValidationFlag: (in category 'plugin support-private') -----
+ accessIntegerClass: splArrayIdx withValidationFlag: validationFlag
+ 	"Answer an integer array class from somewhere in the specialObjectsArray, if it appears
+ 	 to be a class, otherwise nilObj.  Make delivering the answer fast since this is used for
+ 	 allocations by using a flag to indicate that validation has already been done.  The
+ 	 validation flags are cleared if the specialObjectsArray is becomed or scavenged."
+ 	<inline: #always>
+ 	| classOop hash |
+ 	classOop := self splObj: splArrayIdx.
+ 	(validatedIntegerClassFlags anyMask: validationFlag) ifTrue:
+ 		[^classOop].
+ 	((self isImmediate: classOop)
+ 	or: [(hash := self rawHashBitsOf: classOop) = 0
+ 	or: [(self classAtIndex: hash) ~= classOop]]) ifTrue:
+ 		[^nilObj].
+ 	validatedIntegerClassFlags := validatedIntegerClassFlags bitOr: validationFlag.
+ 	^classOop!

Item was added:
+ ----- Method: SpurMemoryManager>>classDoubleByteArray (in category 'plugin support') -----
+ classDoubleByteArray
+ 	^self accessIntegerClass: ClassDoubleByteArray withValidationFlag: ValidatedClassDoubleByteArrayFlag!

Item was added:
+ ----- Method: SpurMemoryManager>>classDoubleWordArray (in category 'plugin support') -----
+ classDoubleWordArray
+ 	^self accessIntegerClass: ClassDoubleWordArray withValidationFlag: ValidatedClassDoubleWordArrayFlag!

Item was added:
+ ----- Method: SpurMemoryManager>>classFloat32Array (in category 'plugin support') -----
+ classFloat32Array
+ 	^nilObj
+ 	"should be this but we haven't assigned unused specialObjectArray indices yet
+ 		^self accessIntegerClass: ClassFloat32Array withValidationFlag: ValidatedClassFloat32ArrayFlag"!

Item was added:
+ ----- Method: SpurMemoryManager>>classFloat64Array (in category 'plugin support') -----
+ classFloat64Array
+ 	^nilObj
+ 	"should be this but we haven't assigned unused specialObjectArray indices yet
+ 		^self accessIntegerClass: ClassFloat64Array withValidationFlag: ValidatedClassFloat64ArrayFlag"!

Item was added:
+ ----- Method: SpurMemoryManager>>classWordArray (in category 'plugin support') -----
+ classWordArray
+ 	^self accessIntegerClass: ClassWordArray withValidationFlag: ValidatedClassWordArrayFlag!

Item was changed:
  ----- Method: SpurMemoryManager>>followSpecialObjectsOop (in category 'become implementation') -----
  followSpecialObjectsOop
  	(self isForwarded: specialObjectsOop) ifTrue:
+ 		[validatedIntegerClassFlags := 0.
+ 		 specialObjectsOop := self followForwarded: specialObjectsOop].
- 		[specialObjectsOop := self followForwarded: specialObjectsOop].
  	self followForwardedObjectFields: specialObjectsOop toDepth: 0.!

Item was changed:
  ----- Method: SpurMemoryManager>>initialize (in category 'initialization') -----
  initialize
  	"We can put all initializations that set something to 0 or to false here.
  	 In C all global variables are initialized to 0, and 0 is false."
  	remapBuffer := Array new: RemapBufferSize.
  	remapBufferCount := extraRootCount := 0. "see below"
  	freeListsMask := totalFreeOldSpace := lowSpaceThreshold := 0.
  	checkForLeaks := 0.
  	needGCFlag := signalLowSpace := marking := false.
+ 	becomeEffectsFlags := gcPhaseInProgress := validatedIntegerClassFlags := 0.
- 	becomeEffectsFlags := gcPhaseInProgress := 0.
  	statScavenges := statIncrGCs := statFullGCs := 0.
  	statMaxAllocSegmentTime := 0.
  	statMarkUsecs := statSweepUsecs := statScavengeGCUsecs := statIncrGCUsecs := statFullGCUsecs := statCompactionUsecs := statGCEndUsecs := gcSweepEndUsecs := 0.
  	statSGCDeltaUsecs := statIGCDeltaUsecs := statFGCDeltaUsecs := 0.
  	statGrowMemory := statShrinkMemory := statRootTableCount := statAllocatedBytes := 0.
  	statRootTableOverflows := statMarkCount := statCompactPassCount := statCoalesces := 0.
  
  	"We can initialize things that are allocated but are lazily initialized."
  	unscannedEphemerons := SpurContiguousObjStack new.
  
  	"we can initialize things that are virtual in C."
  	scavenger := SpurGenerationScavenger simulatorClass new manager: self; yourself.
  	segmentManager := SpurSegmentManager simulatorClass new manager: self; yourself.
  	compactor := self class compactorClass simulatorClass new manager: self; yourself.
  
  	"We can also initialize here anything that is only for simulation."
  	heapMap := CogCheck32BitHeapMap new.
  
  	"N.B. We *don't* initialize extraRoots because we don't simulate it."
  	maxOldSpaceSize := self class initializationOptions
  							ifNotNil: [:initOpts| initOpts at: #maxOldSpaceSize ifAbsent: [0]]
  							ifNil: [0]!

Item was changed:
  ----- Method: SpurMemoryManager>>mapExtraRoots (in category 'gc - global') -----
  mapExtraRoots
  	(self shouldRemapObj: specialObjectsOop) ifTrue:
+ 		[validatedIntegerClassFlags := 0.
+ 		 specialObjectsOop := self remapObj: specialObjectsOop].
- 		[specialObjectsOop := self remapObj: specialObjectsOop].
  	self assert: remapBufferCount = 0.
  	"1 to: remapBufferCount do:
  		[:i | | oop |
  		oop := remapBufferCount at: i.
  		((self isImmediate: oop) or: [self isFreeObject: oop]) ifFalse:
  			[(self shouldRemapObj: oop) ifTrue:
  				[remapBuffer at: i put: (self remapObj: oop)]]]."
  	1 to: extraRootCount do:
  		[:i | | oop |
  		oop := (extraRoots at: i) at: 0.
  		((self isImmediate: oop) or: [self isFreeObject: oop]) ifFalse:
  			[(self shouldRemapObj: oop) ifTrue:
  				[(extraRoots at: i) at: 0 put: (self remapObj: oop)]]]!

Item was changed:
  ----- Method: StackInterpreter class>>initializePrimitiveTable (in category 'initialization') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StackInterpreter class>>vmProxyMajorVersion (in category 'api version') -----
- vmProxyMajorVersion
- 	"Define the  VM_PROXY_MAJOR version for this VM as used to
- 	 define the api in platforms/Cross/vm/sqVirtualMachine.[ch]"
- 	^1!

Item was removed:
- ----- Method: StackInterpreter class>>vmProxyMinorVersion (in category 'api version') -----
- vmProxyMinorVersion
- 	"Define the  VM_PROXY_MINOR version for this VM as used to
- 	 define the api in platforms/Cross/vm/sqVirtualMachine.[ch]"
- 	"14 primitiveFailForOSError: methodReturnReceiver: primitiveFailForFFIException:at: added"
- 	^15 "isBooleanObject isPositiveMachineIntegerObject added"!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveAllVMParameters: (in category 'system control primitives') -----
  primitiveAllVMParameters: paramsArraySize
  	"See primitiveVMParameter method comment"
  
  	| result |
  	result := objectMemory instantiateClass: (objectMemory splObj: ClassArray) indexableSize: paramsArraySize.
  	objectMemory storePointerUnchecked: 0	ofObject: result withValue: (self positiveMachineIntegerFor: objectMemory oldSpaceSize).
  	objectMemory storePointerUnchecked: 1	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory newSpaceSize).
  	objectMemory storePointerUnchecked: 2	ofObject: result withValue: (self positiveMachineIntegerFor: objectMemory totalMemorySize).
  	"objectMemory storePointerUnchecked: 3	ofObject: result withValue: objectMemory nilObject was allocationCount".
  	"objectMemory storePointerUnchecked: 4	ofObject: result withValue: objectMemory nilObject allocationsBetweenGCs".
  	objectMemory storePointerUnchecked: 5	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory tenuringThreshold).
  	objectMemory storePointerUnchecked: 6	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statFullGCs).
  	objectMemory storePointerUnchecked: 7	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statFullGCUsecs + 500 // 1000).
  	objectMemory
  		storePointerUnchecked: 8
  		ofObject: result
  		withValue: (objectMemory integerObjectOf: (objectMemory hasSpurMemoryManagerAPI
  														ifTrue: [objectMemory statScavenges]
  														ifFalse: [objectMemory statIncrGCs])).
  	objectMemory
  		storePointerUnchecked: 9
  		ofObject: result
  		withValue: (objectMemory integerObjectOf: (objectMemory hasSpurMemoryManagerAPI
  														ifTrue: [objectMemory statScavengeGCUsecs]
  														ifFalse: [objectMemory statIncrGCUsecs]) + 500 // 1000).
  	objectMemory storePointerUnchecked: 10	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statTenures).
  	"JITTER VM info unused; 11 - 14/12 - 15 available for reuse"
  	11 to: 18 do:
  		[:i | objectMemory storePointerUnchecked: i ofObject: result withValue: ConstZero].
  	objectMemory storePointerUnchecked: 15 ofObject: result withValue: (objectMemory positive64BitIntegerFor: statIdleUsecs).
  	(SistaVM and: [self isCog]) ifTrue:
  		[objectMemory storePointerUnchecked: 16 ofObject: result withValue: (objectMemory floatObjectOf: self getCogCodeZoneThreshold)].
  	objectMemory hasSpurMemoryManagerAPI ifTrue:
  		[objectMemory
  			storePointerUnchecked: 17	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statCompactionUsecs + 500 // 1000);
  			storePointerUnchecked: 18	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory scavengeThresholdAsExtent)].
  	objectMemory storePointerUnchecked: 19	ofObject: result withValue: (objectMemory positive64BitIntegerFor: self ioUTCStartMicroseconds).
  	objectMemory storePointerUnchecked: 20	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory rootTableCount).
  	objectMemory storePointerUnchecked: 21	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statRootTableOverflows).
  	objectMemory storePointerUnchecked: 22	ofObject: result withValue: (objectMemory integerObjectOf: extraVMMemory).
  	objectMemory storePointerUnchecked: 23	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory shrinkThreshold).
  	objectMemory storePointerUnchecked: 24	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory growHeadroom).
  	objectMemory storePointerUnchecked: 25	ofObject: result withValue: (objectMemory integerObjectOf: self ioHeartbeatMilliseconds).
  	objectMemory storePointerUnchecked: 26	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statMarkCount).
  	objectMemory storePointerUnchecked: 27	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statSweepCount).
  	objectMemory storePointerUnchecked: 28	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statMkFwdCount).
  	objectMemory storePointerUnchecked: 29	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statCompMoveCount).
  	objectMemory storePointerUnchecked: 30	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statGrowMemory).
  	objectMemory storePointerUnchecked: 31	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statShrinkMemory).
  	objectMemory storePointerUnchecked: 32	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statRootTableCount).
  	objectMemory hasSpurMemoryManagerAPI ifTrue: "was statAllocationCount"
  		[objectMemory storePointerUnchecked: 33	ofObject: result withValue: (objectMemory positive64BitIntegerFor: objectMemory currentAllocatedBytes)].
  	objectMemory storePointerUnchecked: 34	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statSurvivorCount).
  	objectMemory storePointerUnchecked: 35	ofObject: result withValue: (objectMemory integerObjectOf: (self microsecondsToMilliseconds: objectMemory statGCEndUsecs)).
  	objectMemory storePointerUnchecked: 36	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statSpecialMarkCount).
  	objectMemory storePointerUnchecked: 37	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statIGCDeltaUsecs + 500 // 1000).
  	objectMemory storePointerUnchecked: 38	ofObject: result withValue: (objectMemory integerObjectOf: statPendingFinalizationSignals).
  	objectMemory storePointerUnchecked: 39	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory wordSize).
  	objectMemory storePointerUnchecked: 40	ofObject: result withValue: (objectMemory integerObjectOf: self imageFormatVersion).
  	objectMemory storePointerUnchecked: 41	ofObject: result withValue: (objectMemory integerObjectOf: numStackPages).
  	objectMemory storePointerUnchecked: 42	ofObject: result withValue: (objectMemory integerObjectOf: desiredNumStackPages).
  	objectMemory storePointerUnchecked: 43	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory edenBytes).
  	objectMemory storePointerUnchecked: 44	ofObject: result withValue: (objectMemory integerObjectOf: desiredEdenBytes).
  	objectMemory storePointerUnchecked: 45	ofObject: result withValue: self getCogCodeSize.
  	objectMemory storePointerUnchecked: 46	ofObject: result withValue: self getDesiredCogCodeSize.
  	objectMemory storePointerUnchecked: 47	ofObject: result withValue: self getCogVMFlags.
  	objectMemory storePointerUnchecked: 48	ofObject: result withValue: (objectMemory integerObjectOf: self ioGetMaxExtSemTableSize).
  	"50 & 51 (49 & 50) reserved for parameters that persist in the image"
  	objectMemory storePointerUnchecked: 51	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory rootTableCapacity).
  	objectMemory hasSpurMemoryManagerAPI ifTrue:
  		[objectMemory
  			storePointerUnchecked: 52 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory numSegments);
  			storePointerUnchecked: 53 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory freeSize);
  			storePointerUnchecked: 54 ofObject: result withValue: (objectMemory floatObjectOf: objectMemory getHeapGrowthToSizeGCRatio)].
  	objectMemory storePointerUnchecked: 55	ofObject: result withValue: (self positive64BitIntegerFor: statProcessSwitch).
  	objectMemory storePointerUnchecked: 56	ofObject: result withValue: (self positive64BitIntegerFor: statIOProcessEvents).
  	objectMemory storePointerUnchecked: 57	ofObject: result withValue: (self positive64BitIntegerFor: statForceInterruptCheck).
  	objectMemory storePointerUnchecked: 58	ofObject: result withValue: (self positive64BitIntegerFor: statCheckForEvents).
  	objectMemory storePointerUnchecked: 59	ofObject: result withValue: (self positive64BitIntegerFor: statStackOverflow).
  	objectMemory storePointerUnchecked: 60	ofObject: result withValue: (self positive64BitIntegerFor: statStackPageDivorce).
  	objectMemory storePointerUnchecked: 61	ofObject: result withValue: self getCodeCompactionCount.
  	objectMemory storePointerUnchecked: 62	ofObject: result withValue: self getCodeCompactionMSecs.
  	objectMemory storePointerUnchecked: 63	ofObject: result withValue: self getCogMethodCount.
  	objectMemory storePointerUnchecked: 64	ofObject: result withValue: self getCogVMFeatureFlags.
  	objectMemory storePointerUnchecked: 65	ofObject: result withValue: (objectMemory integerObjectOf: self stackPageByteSize).
  	objectMemory hasSpurMemoryManagerAPI ifTrue:
  		[objectMemory
  			storePointerUnchecked: 66 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory maxOldSpaceSize)].
  	objectMemory storePointerUnchecked: 67 ofObject: result withValue: (objectMemory floatObjectOf: stackPages statAverageLivePagesWhenMapping).
  	objectMemory storePointerUnchecked: 68 ofObject: result withValue: (objectMemory integerObjectOf: stackPages statMaxPageCountWhenMapping).
+ 	objectMemory storePointerUnchecked: 69 ofObject: result withValue: (objectMemory integerObjectOf: self vmProxyMajorVersion).
+ 	objectMemory storePointerUnchecked: 70 ofObject: result withValue: (objectMemory integerObjectOf: self vmProxyMinorVersion).	
- 	objectMemory
- 		storePointerUnchecked: 69
- 		ofObject: result
- 		withValue: (objectMemory integerObjectOf: (self cCode: 'VM_PROXY_MAJOR' inSmalltalk: [self class vmProxyMajorVersion])).
- 	objectMemory
- 		storePointerUnchecked: 70
- 		ofObject: result
- 		withValue: (objectMemory integerObjectOf: (self cCode: 'VM_PROXY_MINOR' inSmalltalk: [self class vmProxyMinorVersion])).	
  	objectMemory storePointerUnchecked: 71	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statMarkUsecs + 500 // 1000).
  	objectMemory storePointerUnchecked: 72	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statSweepUsecs + 500 // 1000).
  	objectMemory hasSpurMemoryManagerAPI ifTrue:
  		[objectMemory
  			storePointerUnchecked: 73	ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statMaxAllocSegmentTime + 500 // 1000)].
  	objectMemory storePointerUnchecked: 74	ofObject: result withValue: (objectMemory booleanObjectOf: self primitiveDoMixedArithmetic).
  
  	objectMemory beRootIfOld: result.
  	self methodReturnValue: result!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveGetVMParameter: (in category 'system control primitives') -----
  primitiveGetVMParameter: arg 
  	"See primitiveVMParameter method comment.
  	 N.B. written as a returning case to avoid branch limits in the V3 bytecode set."
  	arg caseOf: {
  			[1]  ->	[^self positiveMachineIntegerFor: objectMemory oldSpaceSize].
  			[2]  ->	[^objectMemory integerObjectOf: objectMemory newSpaceSize].
  			[3]  ->	[^self positiveMachineIntegerFor: objectMemory totalMemorySize].
  			[6]  ->	[^objectMemory integerObjectOf: objectMemory tenuringThreshold].
  			[7]  ->	[^objectMemory integerObjectOf: objectMemory statFullGCs].
  			[8]  ->	[^objectMemory integerObjectOf: objectMemory statFullGCUsecs + 500 // 1000].
  			[9]  ->	[^objectMemory integerObjectOf: (objectMemory hasSpurMemoryManagerAPI
  														ifTrue: [objectMemory statScavenges]
  														ifFalse: [objectMemory statIncrGCs])].
  			[10] ->	[^objectMemory integerObjectOf: (objectMemory hasSpurMemoryManagerAPI
  														ifTrue: [objectMemory statScavengeGCUsecs]
  														ifFalse: [objectMemory statIncrGCUsecs]) + 500 // 1000].
  			[11] ->	[^objectMemory integerObjectOf: objectMemory statTenures].
  			[12] ->	[^ConstZero]. "Was JITTER VM info"
  			[13] ->	[^ConstZero]. "Was JITTER VM info"
  			[14] ->	[^ConstZero]. "Was JITTER VM info"
  			[15] ->	[^ConstZero]. "Was JITTER VM info"
  			[16] ->	[^self positive64BitIntegerFor: statIdleUsecs].
  			[17] ->	[^(SistaVM and: [self isCog])
  						ifTrue: [objectMemory floatObjectOf: self getCogCodeZoneThreshold]
  						ifFalse: [ConstZero]].
  			[18] ->	[^objectMemory hasSpurMemoryManagerAPI
  						ifTrue: [objectMemory integerObjectOf: objectMemory statCompactionUsecs + 500 // 1000]
  						ifFalse: [ConstZero]].
  			[19] ->	[^objectMemory hasSpurMemoryManagerAPI
  						ifTrue: [objectMemory integerObjectOf: objectMemory scavengeThresholdAsExtent]
  						ifFalse: [ConstZero]].
  			[20] ->	[^objectMemory positive64BitIntegerFor: self ioUTCStartMicroseconds].
  			[21] ->	[^objectMemory integerObjectOf: objectMemory rootTableCount].
  			[22] ->	[^objectMemory integerObjectOf: objectMemory statRootTableOverflows].
  			[23] ->	[^objectMemory integerObjectOf: extraVMMemory].
  			[24] ->	[^objectMemory integerObjectOf: objectMemory shrinkThreshold].
  			[25] ->	[^objectMemory integerObjectOf: objectMemory growHeadroom].
  			[26] ->	[^objectMemory integerObjectOf: self ioHeartbeatMilliseconds].
  			[27] ->	[^objectMemory integerObjectOf: objectMemory statMarkCount].
  			[28] ->	[^objectMemory integerObjectOf: objectMemory statSweepCount].
  			[29] ->	[^objectMemory integerObjectOf: objectMemory statMkFwdCount].
  			[30] ->	[^objectMemory integerObjectOf: objectMemory statCompMoveCount].
  			[31] ->	[^objectMemory integerObjectOf: objectMemory statGrowMemory].
  			[32] ->	[^objectMemory integerObjectOf: objectMemory statShrinkMemory].
  			[33] ->	[^objectMemory integerObjectOf: objectMemory statRootTableCount].
  			[34] ->	[^objectMemory hasSpurMemoryManagerAPI ifTrue:"was statAllocationCount"
  						[objectMemory positive64BitIntegerFor: objectMemory currentAllocatedBytes]].
  			[35] ->	[^objectMemory integerObjectOf: objectMemory statSurvivorCount].
  			[36] ->	[^objectMemory integerObjectOf: (self microsecondsToMilliseconds: objectMemory statGCEndUsecs)].
  			[37] ->	[^objectMemory integerObjectOf: objectMemory statSpecialMarkCount].
  			[38] ->	[^objectMemory integerObjectOf: objectMemory statIGCDeltaUsecs + 500 // 1000].
  			[39] ->	[^objectMemory integerObjectOf: statPendingFinalizationSignals].
  			[40] ->	[^objectMemory integerObjectOf: objectMemory wordSize].
  			[41] ->	[^objectMemory integerObjectOf: self imageFormatVersion].
  			[42] ->	[^objectMemory integerObjectOf: numStackPages].
  			[43] ->	[^objectMemory integerObjectOf: desiredNumStackPages].
  			[44] ->	[^objectMemory integerObjectOf: objectMemory edenBytes].
  			[45] ->	[^objectMemory integerObjectOf: desiredEdenBytes].
  			[46] ->	[^self getCogCodeSize].
  			[47] ->	[^self getDesiredCogCodeSize].
  			[48] ->	[^self getCogVMFlags].
  			[49] ->	[^objectMemory integerObjectOf: self ioGetMaxExtSemTableSize].
  			[52] ->	[^objectMemory integerObjectOf: objectMemory rootTableCapacity].
  			[53] ->	[^objectMemory hasSpurMemoryManagerAPI ifTrue:
  						[objectMemory integerObjectOf: objectMemory numSegments]].
  			[54] ->	[^objectMemory hasSpurMemoryManagerAPI ifTrue:
  						[objectMemory integerObjectOf: objectMemory freeSize]].
  			[55] ->	[^objectMemory hasSpurMemoryManagerAPI ifTrue:
  						[objectMemory floatObjectOf: objectMemory getHeapGrowthToSizeGCRatio]].
  			[56] ->	[^self positive64BitIntegerFor: statProcessSwitch].
  			[57] ->	[^self positive64BitIntegerFor: statIOProcessEvents].
  			[58] ->	[^self positive64BitIntegerFor: statForceInterruptCheck].
  			[59] ->	[^self positive64BitIntegerFor: statCheckForEvents].
  			[60] ->	[^self positive64BitIntegerFor: statStackOverflow].
  			[61] ->	[^self positive64BitIntegerFor: statStackPageDivorce].
  			[62] ->	[^self getCodeCompactionCount].
  			[63] ->	[^self getCodeCompactionMSecs].
  			[64] ->	[^self getCogMethodCount].
  			[65] ->	[^self getCogVMFeatureFlags].
  			[66] ->	[^objectMemory integerObjectOf: self stackPageByteSize].
  			[67] ->	[^objectMemory hasSpurMemoryManagerAPI ifTrue:
  						[objectMemory integerObjectOf: objectMemory maxOldSpaceSize]].
  			[68] ->	[^objectMemory floatObjectOf: stackPages statAverageLivePagesWhenMapping].
  			[69] ->	[^objectMemory integerObjectOf: stackPages statMaxPageCountWhenMapping].
+ 			[70] ->	[^objectMemory integerObjectOf: self vmProxyMajorVersion].
+ 			[71] ->	[^objectMemory integerObjectOf: self vmProxyMinorVersion].
- 			[70] ->	[^self integerObjectOf: (self cCode: 'VM_PROXY_MAJOR' inSmalltalk: [self class vmProxyMajorVersion])].
- 			[71] ->	[^self integerObjectOf: (self cCode: 'VM_PROXY_MINOR' inSmalltalk: [self class vmProxyMinorVersion])].
  			[72] ->	[^objectMemory integerObjectOf: objectMemory statMarkUsecs + 500 // 1000].
  			[73] ->	[^objectMemory integerObjectOf: objectMemory statSweepUsecs + 500 // 1000].
  			[74] ->	[^objectMemory hasSpurMemoryManagerAPI ifTrue:
  						[objectMemory integerObjectOf: objectMemory statMaxAllocSegmentTime + 500 // 1000]].
  			[75] ->	[^objectMemory booleanObjectOf: self primitiveDoMixedArithmetic] }
  		otherwise: [^nil]!

Item was added:
+ ----- Method: VMClass class>>vmProxyMajorVersion (in category 'plugin api version') -----
+ vmProxyMajorVersion
+ 	"Define the  VM_PROXY_MAJOR version for this VM as used to
+ 	 define the api in platforms/Cross/vm/sqVirtualMachine.[ch]
+ 	 and in interp.h."
+ 	^1!

Item was added:
+ ----- Method: VMClass class>>vmProxyMinorVersion (in category 'plugin api version') -----
+ vmProxyMinorVersion
+ 	"Define the  VM_PROXY_MAJOR version for this VM as used to define
+ 	 the api in platforms/Cross/vm/sqVirtualMachine.[ch] and in interp.h.
+ 	 This should be defined by the objectMemoryClass in use."
+ 	^self subclassResponsibility!

Item was changed:
  ----- Method: VMClass class>>writeVMHeaderTo:bytesPerWord:generator: (in category 'translation') -----
  writeVMHeaderTo: aStream bytesPerWord: bytesPerWord generator: aCCodeGenerator
  	"Generate the contents of interp.h on aStream.  Specific Interpreter subclasses
  	 override to add more stuff."
  	aCCodeGenerator
+ 		putDefineOf: 'VM_PROXY_MAJOR' as: self objectMemoryClass vmProxyMajorVersion on: aStream;
+ 		putDefineOf: 'VM_PROXY_MINOR' as: self objectMemoryClass vmProxyMinorVersion on: aStream.
- 		putDefineOf: 'VM_PROXY_MAJOR' as: self vmProxyMajorVersion on: aStream;
- 		putDefineOf: 'VM_PROXY_MINOR' as: self vmProxyMinorVersion on: aStream.
  	aStream cr.
  	aCCodeGenerator
  		putDefineOf: 'SQ_VI_BYTES_PER_WORD' as: bytesPerWord on: aStream.
  	aStream cr.
  
  	"The most basic constants must be defined here, not in e.g. the plugin sources, to allow those
  	 other sources to be shared between different builds (Spur vs SqueakV3, 32-bit vs 64-bit, etc)"
  	VMBasicConstants mostBasicConstantNames asSet sorted do:
  		[:constName|
  		(VMBasicConstants classPool at: constName ifAbsent: []) ifNotNil:
  			[:const| aCCodeGenerator putDefineOf: constName as: const on: aStream]].
  	aStream cr.
  
  	((VMBasicConstants classPool associations select: [:a| a key beginsWith: 'PrimErr'])
  		sorted: [:a1 :a2| a1 value <= a2 value])
  		do: [:a| aCCodeGenerator putDefineOf: a key as: a value on: aStream].
  	aStream cr.
  
  	aCCodeGenerator
  		putDefineOf: 'MinSmallInteger' as: self objectMemoryClass minSmallInteger on: aStream;
  		putDefineOf: 'MaxSmallInteger' as: self objectMemoryClass maxSmallInteger on: aStream;
  		putDefineOf: 'NumSmallIntegerTagBits' as: self objectMemoryClass numSmallIntegerTagBits on: aStream.
  	aStream cr!

Item was changed:
  ----- Method: VMClass>>minorVersion (in category 'simulation support') -----
  minorVersion
  	"This is implemented in sqVirtualMachine.c, so this form is for simulation only."
  	<doNotGenerate>
+ 	^self class objectMemoryClass vmProxyMinorVersion!
- 	^self class vmProxyMinorVersion!

Item was added:
+ ----- Method: VMClass>>vmProxyMajorVersion (in category 'plugin api version') -----
+ vmProxyMajorVersion
+ 	"Define the  VM_PROXY_MAJOR version for this VM as used to
+ 	 define the api in platforms/Cross/vm/sqVirtualMachine.[ch]
+ 	 and in interp.h."
+ 	<inline: #always>
+ 	^self cCode: [#VM_PROXY_MAJOR] inSmalltalk: [self class objectMemoryClass vmProxyMajorVersion]!

Item was added:
+ ----- Method: VMClass>>vmProxyMinorVersion (in category 'plugin api version') -----
+ vmProxyMinorVersion
+ 	"Define the  VM_PROXY_MINOR version for this VM as used to
+ 	 define the api in platforms/Cross/vm/sqVirtualMachine.[ch]
+ 	 and in interp.h."
+ 	<inline: #always>
+ 	^self cCode: [#VM_PROXY_MINOR] inSmalltalk: [self class objectMemoryClass vmProxyMinorVersion]!

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 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'
- 	classVariableNames: 'ActiveProcessIndex CharacterTable CharacterValueIndex ClassAlien ClassArray ClassBitmap ClassBlockClosure ClassBlockContext ClassByteArray ClassByteString ClassCharacter ClassExternalAddress ClassExternalData ClassExternalFunction ClassExternalLibrary ClassExternalStructure ClassFloat ClassFullBlockClosure ClassLargeNegativeInteger ClassLargePositiveInteger ClassMessage ClassMethodContext ClassMutex ClassPoint ClassSemaphore ClassSmallInteger ClassString ClassUnsafeAlien ClassWeakFinalizer ClosureFirstCopiedValueIndex ClosureIndex ClosureNumArgsIndex ClosureOuterContextIndex ClosureStartPCIndex CompactClasses ConstMinusOne ConstOne ConstTwo ConstZero ExcessSignalsIndex ExternalObjectsArray FalseObject FirstLinkIndex ForeignCallbackProcess FullClosureCompiledBlockIndex FullClosureFirstCopiedValueIndex FullClosureReceiverIndex HeaderIndex InstanceSpecificationIndex InstructionPointerIndex KeyIndex LastLinkIndex LiteralStart LowcodeContextMark LowcodeNativeContex
 tClass 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