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

commits at source.squeak.org commits at source.squeak.org
Thu Dec 30 20:32:55 UTC 2021


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

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

Name: VMMaker.oscog-eem.3123
Author: eem
Time: 30 December 2021, 12:32:45.542223 pm
UUID: 526712ee-56ba-4e11-bd69-6efed7cbb0d9
Ancestors: VMMaker.oscog-eem.3122

Cog: several places can use startPCOfMethodHeader: minstead of startPCOfMethod:
convertToInterpreterFrame: needs to assert validInstructionPointer:..., not just evaluate it.

Interpreter: better to test for a process having a context first in printAllStacks.

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

Item was changed:
  ----- Method: CoInterpreter>>convertToInterpreterFrame: (in category 'frame access') -----
  convertToInterpreterFrame: pcDelta
  	"Convert the top machine code frame to an interpreter frame.  Support for
  	 mustBeBoolean in the RegisterAllocatingCogit and for cloneContext: in shallowCopy
  	 when a code compaction is caused by machine code to bytecode pc mapping."
  
  	|  cogMethod methodHeader methodObj startBcpc |
  	<var: 'cogMethod' type: #'CogBlockMethod *'>
  	<var: 'p' type: #'char *'>
  
  	self assert: (self isMachineCodeFrame: framePointer).
  
  	cogMethod := self mframeCogMethod: framePointer.
  	((self mframeIsBlockActivation: framePointer)
  	 and: [cogMethod cmIsFullBlock not])
  		ifTrue:
  			[methodHeader := (self cCoerceSimple: cogMethod cmHomeMethod to: #'CogMethod *') methodHeader.
  			 methodObj := (self cCoerceSimple: cogMethod cmHomeMethod to: #'CogMethod *') methodObject.
  			 startBcpc := cogMethod startpc]
  		ifFalse:
  			[methodHeader := (self cCoerceSimple: cogMethod to: #'CogMethod *') methodHeader.
  			 methodObj := (self cCoerceSimple: cogMethod to: #'CogMethod *') methodObject.
+ 			 startBcpc := self startPCOfMethodHeader: methodHeader].
- 			 startBcpc := self startPCOfMethod: methodObj].
  
  	"Map the machine code instructionPointer to the interpreter instructionPointer of the branch."
  	instructionPointer := cogit bytecodePCFor: instructionPointer startBcpc: startBcpc in: cogMethod.
  	instructionPointer := methodObj + objectMemory baseHeaderSize + instructionPointer - pcDelta - 1. "pre-decrement"
+ 	self assert: (self validInstructionPointer: instructionPointer inMethod: methodObj framePointer: framePointer).
- 	 self validInstructionPointer: instructionPointer inMethod: methodObj framePointer: framePointer.
  
  	"Make space for the two extra fields in an interpreter frame"
  	stackPointer to: framePointer + FoxMFReceiver by: objectMemory wordSize do:
  		[:p| | oop |
  		 oop := objectMemory longAt: p.
  		 objectMemory
  			longAt: p - objectMemory wordSize - objectMemory wordSize
  			put: (objectMemory longAt: p)].
  	stackPointer := stackPointer - objectMemory wordSize - objectMemory wordSize.
  	"Fill in the fields"
  	objectMemory
  		longAt: framePointer + FoxIFrameFlags
  			put: (self
  					encodeFrameFieldHasContext: (self mframeHasContext: framePointer)
  					isBlock: (self mframeIsBlockActivation: framePointer)
  					numArgs: cogMethod cmNumArgs);
  		longAt: framePointer + FoxIFSavedIP
  			put: instructionPointer;
  		longAt: framePointer + FoxMethod
  			put: methodObj.
  
  	self setMethod: methodObj methodHeader: methodHeader!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>pcDataFor: (in category 'method introspection support') -----
  pcDataFor: cogMethod
  	<var: #cogMethod type: #'CogMethod *'>
  	| cm nSlots nEntries data |
  	cm := cogMethod methodObject.
+ 	nSlots := (objectMemory byteSizeOf: cm) - (self startPCOfMethodHeader: cogMethod methodHeader) * 2 + objectMemory minSlotsForShortening.
- 	nSlots := (objectMemory byteSizeOf: cm) - (self startPCOfMethod: cm) * 2 + objectMemory minSlotsForShortening.
  	data := objectMemory instantiateClass: (objectMemory splObj: ClassArray) indexableSize: nSlots.
  	data ifNil: [^-1].
  	nEntries := cogit mapPCDataFor: cogMethod into: data.
  	nEntries = 0 ifTrue:
  		[^0].
  	nEntries < nSlots ifTrue:
  		[objectMemory shorten: data toIndexableSize: nEntries].
  	^data!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>picDataFor: (in category 'method introspection support') -----
  picDataFor: cogMethod
  	<var: #cogMethod type: #'CogMethod *'>
  	| cm nSlots nEntries data |
  	cm := cogMethod methodObject.
+ 	nSlots := (objectMemory byteSizeOf: cm) - (self startPCOfMethodHeader: cogMethod methodHeader) + objectMemory minSlotsForShortening.
- 	nSlots := (objectMemory byteSizeOf: cm) - (self startPCOfMethod: cm) + objectMemory minSlotsForShortening.
  	data := objectMemory instantiateClass: (objectMemory splObj: ClassArray) indexableSize: nSlots.
  	data ifNil: [^-1].
  	nEntries := cogit picDataFor: cogMethod into: data.
  	nEntries = 0 ifTrue:
  		[^0].
  	nEntries < nSlots ifTrue:
  		[objectMemory shorten: data toIndexableSize: nEntries].
  	^data!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveMinimumUnusedHeadroom (in category 'other primitives') -----
  primitiveMinimumUnusedHeadroom
  	<export: true>
+ 	self methodReturnInteger: self minimumUnusedHeadroom!
- 	self methodReturnValue: (self integerObjectOf: self minimumUnusedHeadroom)!

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 startPCOfMethodHeader: cogHomeMethod methodHeader]
- 					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.
  		  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 changed:
  ----- Method: Cogit>>collectCogMethodConstituent: (in category 'profiling primitives') -----
  collectCogMethodConstituent: cogMethod
  	"Answer a description of the mapping between machine code pointers and bytecode pointers for the Cog Method.
  	 First value is the address of the cog method.
  	 Following values are pairs of machine code pc and bytecode pc"
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #cogBlockMethod type: #'CogBlockMethod *'>
  	| cm nSlots errCode cogBlockMethod address data |
  	(cogMethod cmType = CMMethod) 
  		ifFalse: [^self positiveMachineIntegerFor: cogMethod asUnsignedInteger ].
  	cogBlockMethod := self cCoerceSimple: cogMethod to: #'CogBlockMethod *'.
  	cogBlockMethod stackCheckOffset = 0 "isFrameless ?"
  		ifTrue: [^self positiveMachineIntegerFor: cogMethod asUnsignedInteger].
  	cm := cogMethod methodObject.
+ 	nSlots := ((objectMemory byteSizeOf: cm) - (coInterpreter startPCOfMethodHeader: cm methodHeader)) * 2 + objectMemory minSlotsForShortening + 1."+1 for first address"
- 	nSlots := ((objectMemory byteSizeOf: cm) - (coInterpreter startPCOfMethod: cm)) * 2 + objectMemory minSlotsForShortening + 1."+1 for first address"
  	data := objectMemory instantiateClass: (objectMemory splObj: ClassArray) indexableSize: nSlots.
  	data ifNil: [^nil].
  	coInterpreter pushRemappableOop: data.
  	"The iteration assumes the object is the top remappable oop"
  	address := (self positiveMachineIntegerFor: cogMethod asUnsignedInteger).
  	address ifNil: [coInterpreter popRemappableOop. ^nil].
  	coInterpreter
  		storePointerUnchecked: 0
  		ofObject: coInterpreter topRemappableOop
  		withValue: address.
  	cogConstituentIndex := 1.
  	errCode := self
  		mapFor: cogBlockMethod
  		bcpc: (coInterpreter startPCOfMethod: cogMethod methodObject)
  		performUntil: #collectCogConstituentFor:Annotation:Mcpc:Bcpc:Method:
  		arg: cogMethod asVoidPointer.
  	errCode ~= 0 ifTrue: [coInterpreter popRemappableOop. ^nil].
  	cogConstituentIndex < nSlots ifTrue:
  		[objectMemory shorten: coInterpreter topRemappableOop toIndexableSize: cogConstituentIndex].
  	^coInterpreter popRemappableOop.!

Item was removed:
- ----- Method: Cogit>>method:hasSameCodeAs: (in category 'garbage collection') -----
- method: methodA hasSameCodeAs: methodB
- 	"For the purposes of become: see if the two methods are similar, i.e. can be safely becommed.
- 	 This is pretty strict.  All literals and bytecodes must be identical.  Only trailer bytes and header
- 	  flags can differ."
- 	<inline: false>
- 	| headerA headerB numLitsA endPCA |
- 	headerA := objectMemory methodHeaderOf: methodA.
- 	headerB := objectMemory methodHeaderOf: methodB.
- 	numLitsA := objectMemory literalCountOfMethodHeader: headerA.
- 	endPCA := self endPCOf: methodA.
- 	((coInterpreter argumentCountOfMethodHeader: headerA) ~= (coInterpreter argumentCountOfMethodHeader: headerB)
- 	 or: [(coInterpreter temporaryCountOfMethodHeader: headerA) ~= (coInterpreter temporaryCountOfMethodHeader: headerB)
- 	 or: [(coInterpreter primitiveIndexOfMethod: methodA header: headerA) ~= (coInterpreter primitiveIndexOfMethod: methodB header: headerB)
- 	 or: [numLitsA ~= (objectMemory literalCountOfMethodHeader: headerB)
- 	 or: [endPCA > (objectMemory numBytesOf: methodB)]]]]) ifTrue:
- 		[^false].
- 	 1 to: numLitsA - 1 do:
- 		[:li|
- 		(objectMemory fetchPointer: li ofObject: methodA) ~= (objectMemory fetchPointer: li ofObject: methodB) ifTrue:
- 			[^false]].
- 	(coInterpreter startPCOfMethod: methodA) to: endPCA do:
- 		[:bi|
- 		(objectMemory fetchByte: bi ofObject: methodA) ~= (objectMemory fetchByte: bi ofObject: methodB) ifTrue:
- 			[^false]].
- 	^true!

Item was changed:
  ----- Method: Cogit>>method:hasSameCodeAs:checkPenultimate: (in category 'garbage collection') -----
  method: methodA hasSameCodeAs: methodB checkPenultimate: comparePenultimateLiteral
  	"For the purposes of become: see if the two methods are similar, i.e. can be safely becommed.
  	 This is pretty strict.  All literals and bytecodes must be identical.  Only trailer bytes and header
  	  flags can differ."
  	<inline: false>
  	| headerA headerB numLitsA endPCA |
  	headerA := objectMemory methodHeaderOf: methodA.
  	headerB := objectMemory methodHeaderOf: methodB.
  	numLitsA := objectMemory literalCountOfMethodHeader: headerA.
  	endPCA := self endPCOf: methodA.
  	((coInterpreter argumentCountOfMethodHeader: headerA) ~= (coInterpreter argumentCountOfMethodHeader: headerB)
  	 or: [(coInterpreter temporaryCountOfMethodHeader: headerA) ~= (coInterpreter temporaryCountOfMethodHeader: headerB)
  	 or: [(coInterpreter primitiveIndexOfMethod: methodA header: headerA) ~= (coInterpreter primitiveIndexOfMethod: methodB header: headerB)
  	 or: [numLitsA ~= (objectMemory literalCountOfMethodHeader: headerB)
  	 or: [endPCA > (objectMemory numBytesOf: methodB)]]]]) ifTrue:
  		[^false].
  	 1 to: numLitsA - 1 do:
  		[:li|
  		(objectMemory fetchPointer: li ofObject: methodA) ~= (objectMemory fetchPointer: li ofObject: methodB) ifTrue:
  			[(li < (numLitsA - 1) "If the method doesn't use the penultimate literal then don't fail the comparison."
  			  or: [comparePenultimateLiteral]) ifTrue:
  				[^false]]].
+ 	(coInterpreter startPCOfMethodHeader: headerA) to: endPCA do:
- 	(coInterpreter startPCOfMethod: methodA) to: endPCA do:
  		[:bi|
  		(objectMemory fetchByte: bi ofObject: methodA) ~= (objectMemory fetchByte: bi ofObject: methodB) ifTrue:
  			[^false]].
  	^true!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>methodUsesPrimitiveErrorCode:header: (in category 'compile abstract instructions') -----
  methodUsesPrimitiveErrorCode: aMethodObj header: aMethodHeader
  	"Answer if aMethodObj contains a primitive and uses the primitive error code."
  	<inline: true>
  	^(coInterpreter primitiveIndexOfMethod: aMethodObj header: aMethodHeader) > 0
  	  and: [(coInterpreter longStoreBytecodeForHeader: aMethodHeader)
  			= (objectMemory
+ 				fetchByte: (coInterpreter startPCOfMethodHeader: aMethodHeader) + (coInterpreter sizeOfCallPrimitiveBytecode: aMethodHeader)
- 				fetchByte: (coInterpreter startPCOfMethod: aMethodObj) + (coInterpreter sizeOfCallPrimitiveBytecode: aMethodHeader)
  				ofObject: aMethodObj)]!

Item was changed:
  ----- Method: SistaCogit>>picDataFor:into: (in category 'method introspection') -----
  picDataFor: cogMethod into: arrayObj
  	"Collect the branch and send data for cogMethod, storing it into arrayObj."
  	<api>
  	<var: #cogMethod type: #'CogMethod *'>
  	| errCode |
  	cogMethod stackCheckOffset = 0 ifTrue:
  		[^0].
  	introspectionDataIndex := counterIndex := 0.
  	introspectionData := arrayObj.
  	errCode := self
  					mapFor: (self cCoerceSimple: cogMethod to: #'CogBlockMethod *')
+ 					bcpc: (coInterpreter startPCOfMethodHeader: cogMethod methodHeader)
- 					bcpc: (coInterpreter startPCOfMethod: cogMethod methodObject)
  					performUntil: #picDataFor:Annotation:Mcpc:Bcpc:Method:
  					arg: cogMethod asVoidPointer.
  	errCode ~= 0 ifTrue:
  		[self assert: errCode = PrimErrNoMemory.
  		 ^-1].
  	cogMethod blockEntryOffset ~= 0 ifTrue:
  		[errCode := self blockDispatchTargetsFor: cogMethod
  						perform: #picDataForBlockEntry:Method:
  						arg: cogMethod asInteger.
  		 errCode ~= 0 ifTrue:
  			[self assert: errCode = PrimErrNoMemory.
  			 ^-1]].
  	^introspectionDataIndex!

Item was changed:
  ----- Method: SistaCogitClone>>picDataFor:into: (in category 'method introspection') -----
  picDataFor: cogMethod into: arrayObj
  	"Collect the branch and send data for cogMethod, storing it into arrayObj."
  	<api>
  	<var: #cogMethod type: #'CogMethod *'>
  	| errCode |
  	cogMethod stackCheckOffset = 0 ifTrue:
  		[^0].
  	introspectionDataIndex := counterIndex := 0.
  	introspectionData := arrayObj.
  	errCode := self
  					mapFor: (self cCoerceSimple: cogMethod to: #'CogBlockMethod *')
+ 					bcpc: (coInterpreter startPCOfMethodHeader: cogMethod methodHeader)
- 					bcpc: (coInterpreter startPCOfMethod: cogMethod methodObject)
  					performUntil: #picDataFor:Annotation:Mcpc:Bcpc:Method:
  					arg: cogMethod asVoidPointer.
  	errCode ~= 0 ifTrue:
  		[self assert: errCode = PrimErrNoMemory.
  		 ^-1].
  	cogMethod blockEntryOffset ~= 0 ifTrue:
  		[errCode := self blockDispatchTargetsFor: cogMethod
  						perform: #picDataForBlockEntry:Method:
  						arg: cogMethod asInteger.
  		 errCode ~= 0 ifTrue:
  			[self assert: errCode = PrimErrNoMemory.
  			 ^-1]].
  	^introspectionDataIndex!

Item was changed:
  ----- Method: StackInterpreter>>methodUsesPrimitiveErrorCode: (in category 'primitive support') -----
  methodUsesPrimitiveErrorCode: aMethodObj
  	"Answer if aMethodObj contains a primitive and uses the primitive error code."
  	<inline: true>
  	| methodHeader |
  	methodHeader := objectMemory methodHeaderOf: aMethodObj.
  	^(self primitiveIndexOfMethod: aMethodObj header: methodHeader) > 0
  	  and: [(self longStoreBytecodeForHeader: methodHeader)
  			= (objectMemory
+ 				fetchByte: (self startPCOfMethodHeader: methodHeader) + (self sizeOfCallPrimitiveBytecode: methodHeader)
- 				fetchByte: (self startPCOfMethod: aMethodObj) + (self sizeOfCallPrimitiveBytecode: methodHeader)
  				ofObject: aMethodObj)]!

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 |
  	<inline: false>
  	proc := self activeProcess. "may not be an instance of process. may in exceptional circumstances be nilObject"
  	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"
  	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: '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"
  	objectMemory allObjectsDoSafely:
  		[:obj|
  		 ((objectMemory isPointersNonImm: obj)
  		  and: [(objectMemory numSlotsOf: obj) >= minProcessInstSize
+ 		  and: [(objectMemory isContext: (objectMemory fetchPointer: SuspendedContextIndex ofObject: obj))
+ 		  and: [self is: obj KindOfClass: processClass]]]) ifTrue:
- 		  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]]]!

Item was changed:
  ----- Method: StackInterpreter>>startPCOfMethodHeader: (in category 'compiled methods') -----
  startPCOfMethodHeader: methodHeader
+ 	<api>
  	"Answer the zero-relative index to the initial byte for a method.
  	 Zero-relative version of CompiledMethod>>startpc."
  	^(objectMemory literalCountOfMethodHeader: methodHeader) + LiteralStart * objectMemory bytesPerOop!



More information about the Vm-dev mailing list