[Vm-dev] VM Maker: VMMaker.oscog-WoC.3195.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Jun 21 17:23:15 UTC 2022


Tom Braun uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-WoC.3195.mcz

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

Name: VMMaker.oscog-WoC.3195
Author: WoC
Time: 21 June 2022, 7:15:36.142009 pm
UUID: 2e2c7dd0-3800-4463-ae4f-a62c68245333
Ancestors: VMMaker.oscog-eem.3194

adding pinning primitives (instantiate a pinned object in old space avoiding the overhead of allocating it in new space + become)
adding uninitialized new primitives for 64 bits Spur (including lifting the single header word limitation in the jit)
fix printing of CogAbstractInstruction
fixed comments in 64 bit Spur newWithArg jit
attempt to fix the mac profile plugin for 64 bit arm

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

Item was added:
+ ----- Method: CogAbstractInstruction class>>registerMaskFor:and:and:and:and:and:and:and:and:and:and:and: (in category 'register management') -----
+ registerMaskFor: reg1 and: reg2 and: reg3 and: reg4 and: reg5 and: reg6 and: reg7 and: reg8 and: reg9 and: reg10 and: reg11 and: reg12
+ 	^Cogit basicNew registerMaskFor: reg1 and: reg2 and: reg3 and: reg4 and: reg5 and: reg6 and: reg7 and: reg8 and: reg9 and: reg10 and: reg11 and: reg12!

Item was added:
+ ----- Method: CogAbstractInstruction class>>registerMaskFor:and:and:and:and:and:and:and:and:and:and:and:and:and:and: (in category 'register management') -----
+ registerMaskFor: reg1 and: reg2 and: reg3 and: reg4 and: reg5 and: reg6 and: reg7 and: reg8 and: reg9 and: reg10  and: reg11 and: reg12 and: reg13  and: reg14 and: reg15
+ 	^Cogit basicNew registerMaskFor: reg1 and: reg2 and: reg3 and: reg4 and: reg5 and: reg6 and: reg7 and: reg8 and: reg9 and: reg10 and: reg11 and: reg12 and: reg13 and: reg14 and: reg15!

Item was changed:
  ----- Method: CogAbstractInstruction>>printStateOn: (in category 'printing') -----
  printStateOn: aStream
  	| opcodeName orneryOperands format |
  	<doNotGenerate> "Smalltalk-side only"
  	opcode ifNil:
  		[^self].
  	aStream space; nextPut: $(; nextPutAll: (opcodeName := self class nameForOpcode: opcode).
  	orneryOperands := operands isCObjectAccessor
  							ifTrue: [operands object]
  							ifFalse: [operands].
  	format := ((CogRTLOpcodes classPool includesKey: opcodeName)
  				ifTrue: [CogRTLOpcodes]
  				ifFalse: [self class]) printFormatForOpcodeName: opcodeName.
+ 	(format ifNil: [orneryOperands] ifNotNil: [orneryOperands first: (format size min: orneryOperands size)]) withIndexDo:
- 	(format ifNil: [orneryOperands] ifNotNil: [orneryOperands first: format size]) withIndexDo:
  		[:operand :index|
  		operand ifNotNil:
  			[aStream space.
  			 index >= (orneryOperands identityIndexOf: nil ifAbsent: [orneryOperands size + 1]) ifTrue:
  				[aStream print: index - 1; nextPut: $:].
  			 (format notNil and: ['rf' includes: (format at: index ifAbsent: $-)])
  				ifTrue: [aStream nextPutAll: ((format at: index) = $r
  												ifTrue: [self nameForRegister: operand]
  												ifFalse: [self nameForFPRegister: operand])]
  				ifFalse:
  					[| operandNameOrNil |
  					 operandNameOrNil := operand isInteger ifTrue:
  												[(cogit coInterpreter lookupAddress: operand) ifNil:
  													[objectMemory lookupAddress: operand]].
  					 operandNameOrNil ifNotNil: [aStream nextPut: ${].
  					 aStream print: operand.
  					 (operand isInteger and: [operand > 16 and: [opcode ~= Label]]) ifTrue:
  						[objectMemory wordSize = 8
  							ifTrue:
  								[(operand allMask: 1 << 63) ifTrue:
  									[aStream nextPut: $/; print: operand signedIntFromLong64]]
  							ifFalse:
  								[(operand allMask: 1 << 31) ifTrue:
  									[aStream nextPut: $/; print: operand signedIntFromLong]].
  						 aStream nextPut: $/.
  						 operand printOn: aStream base: 16.
  						 operandNameOrNil ifNotNil:
  							[aStream nextPut: $=; nextPutAll: operandNameOrNil; nextPut: $}]]]]].
  	machineCodeSize ifNotNil:
  		[(machineCodeSize between: 1 and: machineCode size) ifTrue:
  			[0 to: machineCodeSize - 1 by: self codeGranularity do:
  				[:i|
  				 aStream space.
  				 (self machineCodeAt: i)
  					ifNil: [aStream nextPut: $.]
  					ifNotNil:
  						[:mc|
  						mc isInteger
  							ifTrue: [mc printOn: aStream base: 16]
  							ifFalse: [mc printOn: aStream]]]]].
  	address ifNotNil:
  		[aStream space; nextPut: $@.
  		 address printOn: aStream base: 16].
  	aStream nextPut: $)!

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveUninitializedNewWithArg (in category 'primitive generators') -----
+ genPrimitiveUninitializedNewWithArg
+ 	"subclasses override if they can"
+ 	^UnimplementedPrimitive!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveNewWithArg (in category 'primitive generators') -----
  genPrimitiveNewWithArg
  	"Implement primitiveNewWithArg for convenient cases:
  	- the receiver has a hash
  	- the receiver is variable and not compiled method
  	- single word header/num slots < numSlotsMask
  	- the result fits in eden
  	See superclass method for dynamic frequencies of formats.
  	For the moment we implement only arrayFormat, firstByteFormat & firstLongFormat"
  
  	| headerReg fillReg instSpecReg byteSizeReg maxSlots
  	  jumpArrayTooBig jumpByteTooBig jumpLongTooBig
  	  jumpArrayFormat jumpByteFormat jumpBytePrepDone jumpLongPrepDone
  	  jumpUnhashed jumpNElementsNonInt jumpFailCuzFixed jumpNoSpace jumpHasSlots fillLoop skip |
- 	<var: 'skip' type: #'AbstractInstruction *'>
- 	<var: 'fillLoop' type: #'AbstractInstruction *'>	
- 	<var: 'jumpHasSlots' type: #'AbstractInstruction *'>
- 	<var: 'jumpNoSpace' type: #'AbstractInstruction *'>
- 	<var: 'jumpUnhashed' type: #'AbstractInstruction *'>
- 	<var: 'jumpByteFormat' type: #'AbstractInstruction *'>
- 	<var: 'jumpByteTooBig' type: #'AbstractInstruction *'>
- 	<var: 'jumpLongTooBig' type: #'AbstractInstruction *'>
- 	<var: 'jumpArrayFormat' type: #'AbstractInstruction *'>
- 	<var: 'jumpArrayTooBig' type: #'AbstractInstruction *'>
- 	<var: 'jumpFailCuzFixed' type: #'AbstractInstruction *'>
- 	<var: 'jumpBytePrepDone' type: #'AbstractInstruction *'>
- 	<var: 'jumpLongPrepDone' type: #'AbstractInstruction *'>
- 	<var: 'jumpNElementsNonInt' type: #'AbstractInstruction *'>
  
  	NewspeakVM ifTrue:
  		[cogit methodNumArgs = 2 ifTrue:
  			[^self genPrimitiveMirrorNewWithArg]].
  	cogit methodNumArgs ~= 1 ifTrue:
  		[^UnimplementedPrimitive].
  	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
  
  	"header will contain classIndex/class's hash & format & numSlots/fixed size"
  	headerReg := SendNumArgsReg.
  	"Assume there's an available scratch register on 64-bit machines.  This holds the saved numFixedFields and then the value to fill with"
  	fillReg := Extra0Reg.
  	self assert: fillReg > 0.
  	"inst spec will hold class's instance specification and then byte size"
  	instSpecReg := byteSizeReg := ClassReg.
  	"The max slots we'll allocate here are those for a single header"
  	maxSlots := objectMemory numSlotsMask - 1.
  
  	"get freeStart as early as possible so as not to wait later..."
  	cogit MoveAw: objectMemory freeStartAddress R: Arg1Reg.
  	"get class's hash & fail if 0"
  	self genGetHashFieldNonImmOf: ReceiverResultReg into: headerReg.
  	jumpUnhashed := cogit JumpZero: 0.
  	"get index and fail if not a +ve integer"
  	jumpNElementsNonInt := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
  	"get class's format inst var for inst spec (format field)"
  	self genLoadSlot: InstanceSpecificationIndex sourceReg: ReceiverResultReg destReg: instSpecReg.
  	cogit LogicalShiftRightCq: objectMemory fixedFieldsFieldWidth + self numSmallIntegerTagBits R: instSpecReg.
  	cogit AndCq: objectMemory formatMask R: instSpecReg.
  	"Add format to classIndex/format header now"
  	cogit MoveR: instSpecReg R: TempReg.
  	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
  	cogit AddR: TempReg R: headerReg.
  	"get integer value of num fields in fillReg now"
  	cogit MoveR: Arg0Reg R: fillReg.
  	self genConvertSmallIntegerToIntegerInReg: fillReg.
  	"dispatch on format, failing if not variable or if compiled method"
  	cogit CmpCq: objectMemory arrayFormat R: instSpecReg.
  	jumpArrayFormat := cogit JumpZero: 0.
  	cogit CmpCq: objectMemory firstByteFormat R: instSpecReg.
  	jumpByteFormat := cogit JumpZero: 0.
  	cogit CmpCq: objectMemory firstLongFormat R: instSpecReg.
  	jumpFailCuzFixed := cogit JumpNonZero: 0.
  
  	cogit CmpCq: (objectMemory integerObjectOf: maxSlots * 2) R: Arg0Reg.
  	jumpLongTooBig := cogit JumpAbove: 0.
  	"save num elements/slot size to instSpecReg"
  	cogit MoveR: fillReg R: instSpecReg.
  	"compute odd bits and add into headerReg; oddBits := 2 - nElements bitAnd: 1"
  	cogit MoveCq: objectMemory wordSize / 4 R: TempReg.
  	cogit SubR: instSpecReg R: TempReg.
  	cogit AndCq: objectMemory wordSize / 4 - 1 R: TempReg.
  	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
  	cogit AddR: TempReg R: headerReg.
  	"round up num elements to numSlots in instSpecReg"
  	cogit AddCq: objectMemory wordSize / 4 - 1 R: instSpecReg.
  	cogit LogicalShiftRightCq: objectMemory shiftForWord - 2 R: instSpecReg.
  	cogit MoveCq: 0 R: fillReg.
  	jumpLongPrepDone := cogit Jump: 0. "go allocate"
  
  	jumpByteFormat jmpTarget:
  	(cogit CmpCq: (objectMemory integerObjectOf: maxSlots * objectMemory wordSize) R: Arg0Reg).
  	jumpByteTooBig := cogit JumpAbove: 0.
  	"save num elements to instSpecReg"
  	cogit MoveR: fillReg R: instSpecReg.
+ 	"compute odd bits and add into headerReg; oddBits := 8 - nElements bitAnd: 7"
- 	"compute odd bits and add into headerReg; oddBits := 4 - nElements bitAnd: 3"
  	cogit MoveCq: objectMemory wordSize R: TempReg.
  	cogit SubR: instSpecReg R: TempReg.
  	cogit AndCq: objectMemory wordSize - 1 R: TempReg.
  	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
  	cogit AddR: TempReg R: headerReg.
  	"round up num elements to numSlots in instSpecReg"
  	cogit AddCq: objectMemory wordSize - 1 R: instSpecReg.
  	cogit LogicalShiftRightCq: objectMemory shiftForWord R: instSpecReg.
  	cogit MoveCq: 0 R: fillReg.
  	jumpBytePrepDone := cogit Jump: 0. "go allocate"
  
  	jumpArrayFormat jmpTarget:
  		(cogit CmpCq: (objectMemory integerObjectOf: maxSlots) R: Arg0Reg).
  	jumpArrayTooBig := cogit JumpAbove: 0.
  	"save num elements/slot size to instSpecReg"
  	cogit MoveR: fillReg R: instSpecReg.
  	cogit MoveCq: objectMemory nilObject R: fillReg.
  	"fall through to allocate"
  
  	jumpBytePrepDone jmpTarget:
  	(jumpLongPrepDone jmpTarget: cogit Label).
  
  	"store numSlots to headerReg"
  	cogit MoveR: instSpecReg R: TempReg.
  	cogit LogicalShiftLeftCq: objectMemory numSlotsFullShift R: TempReg.
  	cogit AddR: TempReg R: headerReg.
  	"compute byte size; remember 0-sized objects still need 1 slot."
  	cogit CmpCq: 0 R: byteSizeReg. "a.k.a. instSpecReg"
  	jumpHasSlots := cogit JumpNonZero: 0.
  	cogit MoveCq: objectMemory baseHeaderSize * 2 R: byteSizeReg.
  	skip := cogit Jump: 0.
  	jumpHasSlots jmpTarget:
  	(cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: byteSizeReg).
  	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.
  	skip jmpTarget:
  	"check if allocation fits"
  	(cogit AddR: Arg1Reg R: byteSizeReg).
  	cogit CmpCq: objectMemory getScavengeThreshold R: byteSizeReg.
  	jumpNoSpace := cogit JumpAboveOrEqual: 0.
  	"get result, increment freeStart and write it back. Arg1Reg holds new freeStart, the limit of the object"
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	cogit MoveR: byteSizeReg Aw: objectMemory freeStartAddress.
- 	"write other half of header (numSlots/0 identityHash)"
  	cogit MoveR: headerReg Mw: 0 r: ReceiverResultReg.
  	"now fill"
  	cogit LoadEffectiveAddressMw: objectMemory baseHeaderSize r: ReceiverResultReg R: Arg1Reg.
  	fillLoop := 
  	cogit MoveR: fillReg Mw: 0 r: Arg1Reg.
  	cogit AddCq: 8 R: Arg1Reg.
  	cogit CmpR: Arg1Reg R: byteSizeReg.
  	cogit JumpAbove: fillLoop.
  	cogit genPrimReturn.
  	
  	jumpNoSpace jmpTarget:
  	(jumpUnhashed jmpTarget:
  	(jumpFailCuzFixed jmpTarget:
  	(jumpArrayTooBig jmpTarget:
  	(jumpByteTooBig jmpTarget:
  	(jumpLongTooBig jmpTarget:
  	(jumpNElementsNonInt jmpTarget: cogit Label)))))).
  
  	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveUninitializedNewWithArg (in category 'primitive generators') -----
+ genPrimitiveUninitializedNewWithArg
+ 	"Implement primitiveUninitializedNewWithArg for convenient cases:
+ 	- the receiver has a hash
+ 	- the receiver is variable and not compiled method
+ 	- the result fits in eden
+ 	See superclass method for dynamic frequencies of formats.
+ 	For the moment we implement only arrayFormat, firstByteFormat & firstLongFormat"
+ 
+ 	| headerReg fillReg instSpecReg byteSizeReg maxSlots
+ 	  jumpByteTooBig jumpLongTooBig
+ 	  jumpByteFormat jumpLongPrepDone
+ 	  jumpUnhashed jumpNElementsNonInt jumpFailCuzFixed jumpNoSpace jumpHasSlots skip jumpDoubleWordPrepDone jumpDoubleBytePrepDone jumpDoubleByteFormat jumpDoubleWordFormat jumpOverflowHeader jumpNoSpaceBigObjects jumpDoubleWordTooBig jumpShortTooBig |
+ 
+ 	NewspeakVM ifTrue:
+ 		[cogit methodNumArgs = 2 ifTrue:
+ 			[^self genPrimitiveMirrorNewWithArg]].
+ 	cogit methodNumArgs ~= 1 ifTrue:
+ 		[^UnimplementedPrimitive].
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 
+ 	"header will contain classIndex/class's hash & format & numSlots/fixed size"
+ 	headerReg := SendNumArgsReg.
+ 	"Assume there's an available scratch register on 64-bit machines.  This holds the saved numFixedFields and then the value to fill with"
+ 	fillReg := Extra0Reg.
+ 	self assert: fillReg > 0.
+ 	"inst spec will hold class's instance specification and then byte size"
+ 	instSpecReg := byteSizeReg := ClassReg.
+ 	"Allow a max of 1 MB"
+ 	maxSlots := objectMemory maxSlotsForNewSpaceAlloc.
+ 
+ 	"get freeStart as early as possible so as not to wait later..."
+ 	cogit MoveAw: objectMemory freeStartAddress R: Arg1Reg.
+ 	"get class's hash & fail if 0"
+ 	self genGetHashFieldNonImmOf: ReceiverResultReg into: headerReg.
+ 	jumpUnhashed := cogit JumpZero: 0.
+ 	"get index and fail if not a +ve integer"
+ 	jumpNElementsNonInt := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	"get class's format inst var for inst spec (format field)"
+ 	self genLoadSlot: InstanceSpecificationIndex sourceReg: ReceiverResultReg destReg: instSpecReg.
+ 	cogit LogicalShiftRightCq: objectMemory fixedFieldsFieldWidth + self numSmallIntegerTagBits R: instSpecReg.
+ 	cogit AndCq: objectMemory formatMask R: instSpecReg.
+ 	"Add format to classIndex/format header now"
+ 	cogit MoveR: instSpecReg R: TempReg.
+ 	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
+ 	cogit AddR: TempReg R: headerReg.
+ 	"get integer value of num fields in fillReg now"
+ 	cogit MoveR: Arg0Reg R: fillReg.
+ 	self genConvertSmallIntegerToIntegerInReg: fillReg.
+ 	"dispatch on format, failing if not a byte format"
+ 	cogit CmpCq: objectMemory firstByteFormat R: instSpecReg.
+ 	jumpByteFormat := cogit JumpZero: 0.
+ 	cogit CmpCq: objectMemory firstShortFormat R: instSpecReg.
+ 	jumpDoubleByteFormat := cogit JumpZero: 0.
+ 	cogit CmpCq: objectMemory sixtyFourBitIndexableFormat R: instSpecReg.
+ 	jumpDoubleWordFormat := cogit JumpZero: 0.
+ 	cogit CmpCq: objectMemory firstLongFormat R: instSpecReg.
+ 	jumpFailCuzFixed := cogit JumpNonZero: 0.
+ 
+ 	"allocates a 32-bit array"
+ 	cogit CmpCq: (objectMemory integerObjectOf: maxSlots * 2) R: Arg0Reg.
+ 	jumpLongTooBig := cogit JumpAbove: 0.
+ 	"save num elements/slot size to instSpecReg"
+ 	cogit MoveR: fillReg R: instSpecReg.
+ 	"compute odd bits and add into headerReg; oddBits := 2 - nElements bitAnd: 1"
+ 	cogit MoveCq: objectMemory wordSize / 4 R: TempReg.
+ 	cogit SubR: instSpecReg R: TempReg.
+ 	cogit AndCq: objectMemory wordSize / 4 - 1 R: TempReg.
+ 	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
+ 	cogit AddR: TempReg R: headerReg.
+ 	"round up num elements to numSlots in instSpecReg; (numElements / 2) ceiling"
+ 	cogit AddCq: objectMemory wordSize / 4 - 1 R: instSpecReg.
+ 	cogit LogicalShiftRightCq: objectMemory shiftForWord - 2 R: instSpecReg.
+ 	jumpLongPrepDone := cogit Jump: 0. "go allocate"
+ 	
+ 	"allocates a 16-bit array"
+ 	jumpDoubleByteFormat jmpTarget:
+ 	(cogit CmpCq: (objectMemory integerObjectOf: maxSlots * 4) R: Arg0Reg).
+ 	jumpShortTooBig := cogit JumpAbove: 0.
+ 	"save num elements to instSpecReg"
+ 	cogit MoveR: fillReg R: instSpecReg.
+ 	"compute odd bits and add into headerReg; oddBits := 4 - nElements bitAnd: 3"
+ 	cogit MoveCq: objectMemory wordSize / 2 R: TempReg.
+ 	cogit SubR: instSpecReg R: TempReg.
+ 	cogit AndCq: objectMemory wordSize / 2 - 1 R: TempReg.
+ 	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
+ 	cogit AddR: TempReg R: headerReg.
+ 	"round up num elements to numSlots in instSpecReg; (numElements / 4) ceiling"
+ 	cogit AddCq: objectMemory wordSize / 2 - 1 R: instSpecReg.
+ 	cogit LogicalShiftRightCq: objectMemory shiftForWord - 1 R: instSpecReg.
+ 	jumpDoubleBytePrepDone := cogit Jump: 0. "go allocate"
+ 	
+ 	"allocates a 64-bit array"
+ 	jumpDoubleWordFormat jmpTarget:
+ 	(cogit CmpCq: (objectMemory integerObjectOf: maxSlots) R: Arg0Reg).
+ 	jumpDoubleWordTooBig := cogit JumpAbove: 0.
+ 	"save num elements to instSpecReg"
+ 	cogit MoveR: fillReg R: instSpecReg.
+ 	jumpDoubleWordPrepDone := cogit Jump: 0. "go allocate"
+ 
+ 	"allocates a byte array"
+ 	jumpByteFormat jmpTarget:
+ 	(cogit CmpCq: (objectMemory integerObjectOf: maxSlots * objectMemory wordSize) R: Arg0Reg).
+ 	jumpByteTooBig := cogit JumpAbove: 0.
+ 	"save num elements to instSpecReg"
+ 	cogit MoveR: fillReg R: instSpecReg.
+ 	"compute odd bits and add into headerReg; oddBits := 8 - nElements bitAnd: 7"
+ 	cogit MoveCq: objectMemory wordSize R: TempReg.
+ 	cogit SubR: instSpecReg R: TempReg.
+ 	cogit AndCq: objectMemory wordSize - 1 R: TempReg.
+ 	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
+ 	cogit AddR: TempReg R: headerReg.
+ 	"round up num elements to numSlots in instSpecReg; (numElements / 8) ceiling"
+ 	cogit AddCq: objectMemory wordSize - 1 R: instSpecReg.
+ 	cogit LogicalShiftRightCq: objectMemory shiftForWord R: instSpecReg.
+ 	"fall through to allocate"
+ 
+ 	jumpDoubleWordPrepDone jmpTarget:
+ 	(jumpDoubleBytePrepDone jmpTarget:
+ 	(jumpLongPrepDone jmpTarget: cogit Label)).
+ 
+ 	"if numSlots >= 255 -> overflow header -> handle it"
+ 	cogit CmpCq: objectMemory numSlotsMask R: instSpecReg.
+ 	jumpOverflowHeader := cogit JumpAboveOrEqual: 0.
+ 	"fallthrough: allocate objects with < 255 slots"
+ 	
+ 	"store numSlots to headerReg"
+ 	cogit MoveR: instSpecReg R: TempReg.
+ 	cogit LogicalShiftLeftCq: objectMemory numSlotsFullShift R: TempReg.
+ 	cogit AddR: TempReg R: headerReg.
+ 	"compute byte size; remember 0-sized objects still need 1 slot."
+ 	cogit CmpCq: 0 R: byteSizeReg. "a.k.a. instSpecReg"
+ 	jumpHasSlots := cogit JumpNonZero: 0.
+ 	cogit MoveCq: objectMemory baseHeaderSize * 2 R: byteSizeReg.
+ 	skip := cogit Jump: 0.
+ 	jumpHasSlots jmpTarget:
+ 	(cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: byteSizeReg).
+ 	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.
+ 	skip jmpTarget:
+ 	"check if allocation fits"
+ 	(cogit AddR: Arg1Reg R: byteSizeReg).
+ 	cogit CmpCq: objectMemory getScavengeThreshold R: byteSizeReg.
+ 	jumpNoSpace := cogit JumpAboveOrEqual: 0.
+ 	"get result, increment freeStart and write it back. Arg1Reg holds new freeStart, the limit of the object"
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 	cogit MoveR: byteSizeReg Aw: objectMemory freeStartAddress.
+ 	"write other half of header (numSlots/0 identityHash)"
+ 	cogit MoveR: headerReg Mw: 0 r: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	
+ 	"allocate object with up to 1 << 16 - 1 slots; numSlots >= 255"
+ 	"store always 255 to headerReg"
+ 	jumpOverflowHeader jmpTarget:
+ 	(cogit MoveCq: 255 R: TempReg).
+ 	cogit LogicalShiftLeftCq: objectMemory numSlotsFullShift R: TempReg.
+ 	cogit AddR: TempReg R: headerReg.
+ 	"calculate overflow header; Temp Reg can be resued as it already contains 255 as needed"
+ 	cogit AddR: instSpecReg R: TempReg.
+ 	"compute byte size"
+ 	cogit AddCq: (objectMemory baseHeaderSize * 2) / objectMemory wordSize R: byteSizeReg.
+ 	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.
+ 	"check if allocation fits"
+ 	cogit AddR: Arg1Reg R: byteSizeReg.
+ 	cogit CmpCq: objectMemory getScavengeThreshold R: byteSizeReg.
+ 	jumpNoSpaceBigObjects := cogit JumpAboveOrEqual: 0.
+ 	"get result, increment freeStart and write it back. Arg1Reg holds new freeStart, the limit of the object"
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 	cogit MoveR: byteSizeReg Aw: objectMemory freeStartAddress.
+ 	"write overflow part"
+ 	cogit MoveR: TempReg Mw: 0 r: ReceiverResultReg.
+ 	"write header"
+ 	cogit MoveR: headerReg Mw: objectMemory baseHeaderSize r: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 	
+ 	jumpShortTooBig jmpTarget:
+ 	(jumpDoubleWordTooBig jmpTarget:
+ 	(jumpNoSpaceBigObjects jmpTarget:
+ 	(jumpNoSpace jmpTarget:
+ 	(jumpUnhashed jmpTarget:
+ 	(jumpFailCuzFixed jmpTarget:
+ 	(jumpByteTooBig jmpTarget:
+ 	(jumpLongTooBig jmpTarget:
+ 	(jumpNElementsNonInt jmpTarget: cogit Label)))))))).
+ 
+ 	^0!

Item was added:
+ ----- Method: Cogit>>registerMaskFor:and:and:and:and:and:and:and:and:and:and:and: (in category 'register management') -----
+ registerMaskFor: reg1 and: reg2 and: reg3 and: reg4 and: reg5 and: reg6 and: reg7 and: reg8 and: reg9 and: reg10  and: reg11 and: reg12
+ 	<inline: true>
+ 	^((((((((((1 << reg1 bitOr: 1 << reg2) bitOr: 1 << reg3) bitOr: 1 << reg4) bitOr: 1 << reg5) bitOr: 1 << reg6) bitOr: 1 << reg7) bitOr: 1 << reg8) bitOr: 1 << reg9) bitOr: 1 << reg10) bitOr: 1 << reg11) bitOr: 1 << reg12!

Item was added:
+ ----- Method: Cogit>>registerMaskFor:and:and:and:and:and:and:and:and:and:and:and:and:and:and: (in category 'register management') -----
+ registerMaskFor: reg1 and: reg2 and: reg3 and: reg4 and: reg5 and: reg6 and: reg7 and: reg8 and: reg9 and: reg10  and: reg11 and: reg12 and: reg13  and: reg14 and: reg15
+ 	<inline: true>
+ 	^(((((((((((((1 << reg1 bitOr: 1 << reg2) bitOr: 1 << reg3) bitOr: 1 << reg4) bitOr: 1 << reg5) bitOr: 1 << reg6) bitOr: 1 << reg7) bitOr: 1 << reg8) bitOr: 1 << reg9) bitOr: 1 << reg10) bitOr: 1 << reg11) bitOr: 1 << reg12) bitOr: 1 << reg13) bitOr: 1 << reg14) bitOr: 1 << reg15!

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

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveNewPinnedInOldSpace (in category 'object access primitives') -----
+ primitiveNewPinnedInOldSpace
+ 	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
+ 		[(argumentCount < 1
+ 		  or: [self objCouldBeClassObj: self stackTop]) ifFalse:
+ 			[^self primitiveFailFor: PrimErrBadArgument]].
+ 	objectMemory hasSpurMemoryManagerAPI
+ 		ifTrue:
+ 			["Allocate a new fixed-size instance.  Fail if the allocation would leave
+ 			  less than lowSpaceThreshold bytes free. This *will not* cause a GC :-)"
+ 			(objectMemory instantiateClass: self stackTop)
+ 				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
+ 				ifNil: [self primitiveFailFor: ((objectMemory isFixedSizePointerFormat: (objectMemory instSpecOfClass: self stackTop))
+ 											ifTrue: [PrimErrNoMemory]
+ 											ifFalse: [PrimErrBadReceiver])]]
+ 		ifFalse:
+ 			["Allocate a new fixed-size instance. Fail if the allocation would leave
+ 			  less than lowSpaceThreshold bytes free. May cause a GC."
+ 			| spaceOkay |
+ 			"The following may cause GC!! Use var for result to permit inlining."
+ 			spaceOkay := objectMemory
+ 								sufficientSpaceToInstantiate: self stackTop
+ 								indexableSize: 0.
+ 			spaceOkay
+ 				ifTrue:
+ 					[self
+ 						pop: argumentCount + 1
+ 						thenPush: (objectMemory
+ 									instantiateClass: self stackTop
+ 									indexableSize: 0)]
+ 				ifFalse: [self primitiveFailFor: PrimErrNoMemory]]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveNewWithArgUninitialized (in category 'object access primitives') -----
+ primitiveNewWithArgUninitialized
+ 	"Allocate a new indexable instance. Fail if the allocation would leave less than lowSpaceThreshold bytes free. May cause a GC."
+ 	| size spaceOkay instSpec |
+ 	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
+ 		[(argumentCount < 2
+ 		  or: [self addressCouldBeClassObj: (self stackValue: 1)]) ifFalse:
+ 			[^self primitiveFailFor: PrimErrBadArgument]].
+ 	size := self positiveMachineIntegerValueOf: self stackTop.
+ 	self successful ifFalse:"positiveMachineIntegerValueOf: succeeds only for non-negative integers."
+ 		[^self primitiveFailFor: PrimErrBadArgument].
+ 	objectMemory hasSpurMemoryManagerAPI
+ 		ifTrue:
+ 			[(objectMemory instantiateUninitializedClass: (self stackValue: 1) indexableSize: size)
+ 				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
+ 				ifNil: [instSpec := objectMemory instSpecOfClass: (self stackValue: 1).
+ 					  self primitiveFailFor: (((objectMemory isIndexableFormat: instSpec)
+ 											and: [(objectMemory isCompiledMethodFormat: instSpec) not])
+ 												ifTrue: [PrimErrNoMemory]
+ 												ifFalse: [PrimErrBadReceiver])]]
+ 		ifFalse:
+ 			[spaceOkay := objectMemory sufficientSpaceToInstantiate: (self stackValue: 1) indexableSize: size.
+ 			 spaceOkay
+ 				ifTrue:
+ 					[self
+ 						pop: argumentCount + 1
+ 						thenPush: (objectMemory instantiateClass: (self stackValue: 1) indexableSize: size)]
+ 				ifFalse:
+ 					[self primitiveFailFor: PrimErrNoMemory]]!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializePrimitiveTableForSqueak (in category 'class initialization') -----
  initializePrimitiveTableForSqueak
  	"Initialize the table of primitive generators.  This does not include normal primitives implemented in the coInterpreter.
  	 N.B. primitives that don't have an explicit arg count (the integer following the generator) may be variadic."
  	"SimpleStackBasedCogit initializePrimitiveTableForSqueak"
  	MaxCompiledPrimitiveIndex := self objectRepresentationClass wordSize = 8
+ 										ifTrue: [580]
+ 										ifFalse: [580].
- 										ifTrue: [575]
- 										ifFalse: [575].
  	primitiveTable := CArrayAccessor on: (Array new: MaxCompiledPrimitiveIndex + 1).
  	self table: primitiveTable from: 
  	#(	"Integer Primitives (0-19)"
  		(1 genPrimitiveAdd				1)
  		(2 genPrimitiveSubtract		1)
  		(3 genPrimitiveLessThan		1)
  		(4 genPrimitiveGreaterThan		1)
  		(5 genPrimitiveLessOrEqual		1)
  		(6 genPrimitiveGreaterOrEqual	1)
  		(7 genPrimitiveEqual			1)
  		(8 genPrimitiveNotEqual		1)
  		(9 genPrimitiveMultiply			1)
  		(10 genPrimitiveDivide			1)
  		(11 genPrimitiveMod			1)
  		(12 genPrimitiveDiv				1)
  		(13 genPrimitiveQuo			1)
  		(14 genPrimitiveBitAnd			1)
  		(15 genPrimitiveBitOr			1)
  		(16 genPrimitiveBitXor			1)
  		(17 genPrimitiveBitShift		1)
  		(18 genPrimitiveMakePoint		1)	"this is here mainly to remove noise from printPrimTraceLog()"
  		"(19 primitiveFail)"					"Guard primitive for simulation -- *must* fail"
  
  		"LargeInteger Primitives (20-39)"
  		"(20 primitiveFail)"
  		"(21 primitiveAddLargeIntegers)"
  		"(22 primitiveSubtractLargeIntegers)"
  		"(23 primitiveLessThanLargeIntegers)"
  		"(24 primitiveGreaterThanLargeIntegers)"
  		"(25 primitiveLessOrEqualLargeIntegers)"
  		"(26 primitiveGreaterOrEqualLargeIntegers)"
  		"(27 primitiveEqualLargeIntegers)"
  		"(28 primitiveNotEqualLargeIntegers)"
  		"(29 primitiveMultiplyLargeIntegers)"
  		"(30 primitiveDivideLargeIntegers)"
  		"(31 primitiveModLargeIntegers)"
  		"(32 primitiveDivLargeIntegers)"
  		"(33 primitiveQuoLargeIntegers)"
  		"(34 primitiveBitAndLargeIntegers)"
  		"(35 primitiveBitOrLargeIntegers)"
  		"(36 primitiveBitXorLargeIntegers)"
  		"(37 primitiveBitShiftLargeIntegers)"
  
  		"Float Primitives (38-59)"
  		"(38 genPrimitiveFloatAt)"
  		"(39 genPrimitiveFloatAtPut)"
  		(40 genPrimitiveAsFloat					0)
  		(41 genPrimitiveFloatAdd				1)
  		(42 genPrimitiveFloatSubtract			1)
  		(43 genPrimitiveFloatLessThan			1)
  		(44 genPrimitiveFloatGreaterThan		1)
  		(45 genPrimitiveFloatLessOrEqual		1)
  		(46 genPrimitiveFloatGreaterOrEqual	1)
  		(47 genPrimitiveFloatEqual				1)
  		(48 genPrimitiveFloatNotEqual			1)
  		(49 genPrimitiveFloatMultiply			1)
  		(50 genPrimitiveFloatDivide				1)
  		"(51 genPrimitiveTruncated)"
  		"(52 genPrimitiveFractionalPart)"
  		"(53 genPrimitiveExponent)"
  		"(54 genPrimitiveTimesTwoPower)"
  		(55 genPrimitiveFloatSquareRoot		0)
  		"(56 genPrimitiveSine)"
  		"(57 genPrimitiveArctan)"
  		"(58 genPrimitiveLogN)"
  		"(59 genPrimitiveExp)"
  
  		"Subscript and Stream Primitives (60-67)"
  		(60 genPrimitiveAt				1)
  		(61 genPrimitiveAtPut			2)
  		(62 genPrimitiveSize			0)
  		(63 genPrimitiveStringAt		1)
  		(64 genPrimitiveStringAtPut	2)
  		"The stream primitives no longer pay their way; normal Smalltalk code is faster."
  		(65 genFastPrimFail)"was primitiveNext"
  		(66 genFastPrimFail) "was primitiveNextPut"
  		(67 genFastPrimFail) "was primitiveAtEnd"
  
  		"StorageManagement Primitives (68-79)"
  		(68 genPrimitiveObjectAt		1)	"Good for debugger/InstructionStream performance"
  		"(69 primitiveObjectAtPut)"
  		(70 genPrimitiveNew			0)
  		(71 genPrimitiveNewWithArg	1)
  		"(72 primitiveArrayBecomeOneWay)"		"Blue Book: primitiveBecome"
  		"(73 primitiveInstVarAt)"
  		"(74 primitiveInstVarAtPut)"
  		(75 genPrimitiveIdentityHash	0)
  		"(76 primitiveStoreStackp)"					"Blue Book: primitiveAsObject"
  		"(77 primitiveSomeInstance)"
  		"(78 primitiveNextInstance)"
  		(79 genPrimitiveNewMethod	2)
  
  		"Control Primitives (80-89)"
  		"(80 primitiveFail)"							"Blue Book: primitiveBlockCopy"
  		"(81 primitiveFail)"							"Blue Book: primitiveValue"
  		"(82 primitiveFail)"							"Blue Book: primitiveValueWithArgs"
  		(83 genPrimitivePerform)
  		"(84 primitivePerformWithArgs)"
  		"(85 primitiveSignal)"
  		"(86 primitiveWait)"
  		"(87 primitiveResume)"
  		"(88 primitiveSuspend)"
  		"(89 primitiveFlushCache)"
  
  		"(90 primitiveMousePoint)"
  		"(91 primitiveTestDisplayDepth)"			"Blue Book: primitiveCursorLocPut"
  		"(92 primitiveSetDisplayMode)"				"Blue Book: primitiveCursorLink"
  		"(93 primitiveInputSemaphore)"
  		"(94 primitiveGetNextEvent)"				"Blue Book: primitiveSampleInterval"
  		"(95 primitiveInputWord)"
  		"(96 primitiveFail)"	"primitiveCopyBits"
  		"(97 primitiveSnapshot)"
  		"(98 primitiveStoreImageSegment)"
  		"(99 primitiveLoadImageSegment)"
  		"(100 primitivePerformInSuperclass)"		"Blue Book: primitiveSignalAtTick"
  		"(101 primitiveBeCursor)"
  		"(102 primitiveBeDisplay)"
  		"(103 primitiveScanCharacters)"
  		"(104 primitiveFail)"	"primitiveDrawLoop"
  		(105 genPrimitiveStringReplace)
  		"(106 primitiveScreenSize)"
  		"(107 primitiveMouseButtons)"
  		"(108 primitiveKbdNext)"
  		"(109 primitiveKbdPeek)"
  
  
  		"System Primitives (110-119)"
  		(110 genPrimitiveIdentical 1)
  		(111 genPrimitiveClass)				"Support both class and Context>>objectClass:"
  		"(112 primitiveBytesLeft)"
  		"(113 primitiveQuit)"
  		"(114 primitiveExitToDebugger)"
  		"(115 primitiveChangeClass)"					"Blue Book: primitiveOopsLeft"
  		"(116 primitiveFlushCacheByMethod)"
  		"(117 primitiveExternalCall)"
  		"(118 primitiveDoPrimitiveWithArgs)"
  		"(119 primitiveFlushCacheSelective)"
  
  		(148 genPrimitiveShallowCopy 0)			"a.k.a. clone"
  
  		(158 genPrimitiveStringCompareWith 1)
  		(159 genPrimitiveHashMultiply 0)
  
  		(165 genPrimitiveIntegerAt			1)	"Signed version of genPrimitiveAt"
  		(166 genPrimitiveIntegerAtPut		2)	"Signed version of genPrimitiveAtPut"
  
  		(169 genPrimitiveNotIdentical 1)
  
  		(170 genPrimitiveAsCharacter)				"SmallInteger>>asCharacter, Character class>>value:"
  		(171 genPrimitiveImmediateAsInteger 0)	"Character>>asInteger/hash/identityHash, SmallFloat64>>identityHash"
  			
  		(173 genPrimitiveSlotAt 1)				"Good for micro-benchmark performance, and for reducing noise in Croquet primitive trace logs"
  		(174 genPrimitiveSlotAtPut 2)			"ditto"
  		(175 genPrimitiveIdentityHash	0)		"Behavior>>identityHash"
  
  		"Old closure primitives"
  		"(186 primitiveFail)" "was primitiveClosureValue"
  		"(187 primitiveFail)" "was primitiveClosureValueWithArgs"
  
  		"Perform method directly"
  		"(188 primitiveExecuteMethodArgsArray)"
  		"(189 primitiveExecuteMethod)"
  
  		"Unwind primitives"
  		"(195 primitiveFindNextUnwindContext)"
  		"(196 primitiveTerminateTo)"
  		"(197 primitiveFindHandlerContext)"
  		(198 genFastPrimFail "primitiveMarkUnwindMethod")
  		(199 genFastPrimFail "primitiveMarkHandlerMethod")
  
  		"new closure primitives"
  		"(200 primitiveClosureCopyWithCopiedValues)"
  		(201 genPrimitiveClosureValue	0) "value"
  		(202 genPrimitiveClosureValue	1) "value:"
  		(203 genPrimitiveClosureValue	2) "value:value:"
  		(204 genPrimitiveClosureValue	3) "value:value:value:"
  		(205 genPrimitiveClosureValue	4) "value:value:value:value:"
  		"(206 genPrimitiveClosureValueWithArgs)" "valueWithArguments:"
  
  		(207 genPrimitiveFullClosureValue) "value[:value:value:value:] et al"
  		"(208 genPrimitiveFullClosureValueWithArgs)" "valueWithArguments:"
  		(209 genPrimitiveFullClosureValue) "valueNoContextSwitch[:value:] et al"
  
  		"(210 primitiveContextAt)"
  		"(211 primitiveContextAtPut)"
  		"(212 primitiveContextSize)"
  
  		"(218 primitiveDoNamedPrimitiveWithArgs)"
  		"(219 primitiveFail)"	"reserved for Cog primitives"
  
  		"(220 primitiveFail)"		"reserved for Cog primitives"
  
  		(221 genPrimitiveClosureValue	0) "valueNoContextSwitch"
  		(222 genPrimitiveClosureValue	1) "valueNoContextSwitch:"
  
  		"SmallFloat primitives (540-559)"
  		(541 genPrimitiveSmallFloatAdd				1)
  		(542 genPrimitiveSmallFloatSubtract			1)
  		(543 genPrimitiveSmallFloatLessThan			1)
  		(544 genPrimitiveSmallFloatGreaterThan		1)
  		(545 genPrimitiveSmallFloatLessOrEqual		1)
  		(546 genPrimitiveSmallFloatGreaterOrEqual		1)
  		(547 genPrimitiveSmallFloatEqual				1)
  		(548 genPrimitiveSmallFloatNotEqual			1)
  		(549 genPrimitiveSmallFloatMultiply				1)
  		(550 genPrimitiveSmallFloatDivide				1)
  		"(551 genPrimitiveSmallFloatTruncated			0)"
  		"(552 genPrimitiveSmallFloatFractionalPart		0)"
  		"(553 genPrimitiveSmallFloatExponent			0)"
  		"(554 genPrimitiveSmallFloatTimesTwoPower	1)"
  		(555 genPrimitiveSmallFloatSquareRoot			0)
  		"(556 genPrimitiveSmallFloatSine				0)"
  		"(557 genPrimitiveSmallFloatArctan				0)"
  		"(558 genPrimitiveSmallFloatLogN				0)"
  		"(559 genPrimitiveSmallFloatExp				0)"
  		(575 genPrimitiveHighBit			0)
+ 		(580 genPrimitiveUninitializedNewWithArg             1)
  	)!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>inOldSpaceInstantiatePinnedClass:indexableSize: (in category 'instantiation') -----
+ inOldSpaceInstantiatePinnedClass: classObj indexableSize: nElements
+ 	<api>
+ 	<var: #nElements type: #usqInt>
+ 	"Allocate an instance of a variable class, excepting CompiledMethod."
+ 	| instSpec classFormat numSlots classIndex newObj fillValue |
+ 	classFormat := self formatOfClass: classObj.
+ 	instSpec := self instSpecOfClassFormat: classFormat.
+ 	classIndex := self rawHashBitsOf: classObj.
+ 	fillValue := 0.
+ 	instSpec caseOf: {
+ 		[self arrayFormat]	->
+ 			[numSlots := nElements.
+ 			 fillValue := nilObj].
+ 		[self indexablePointersFormat]	->
+ 			[numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements.
+ 			 fillValue := nilObj].
+ 		[self weakArrayFormat]	->
+ 			[numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements.
+ 			 fillValue := nilObj].
+ 		[self sixtyFourBitIndexableFormat]	->
+ 			[numSlots := nElements].
+ 		[self firstLongFormat]	->
+ 			[(classIndex = ClassFloatCompactIndex and: [nElements ~= 2]) ifTrue:
+ 				[coInterpreter primitiveFailFor: PrimErrBadReceiver.
+ 				 ^nil].
+ 			 numSlots := nElements + 1 // 2.
+ 			 instSpec := instSpec + (nElements bitAnd: 1)].
+ 		[self firstShortFormat]	->
+ 			[numSlots := nElements + 3 // 4.
+ 			 instSpec := instSpec + (4 - nElements bitAnd: 3)].
+ 		[self firstByteFormat]	->
+ 			[numSlots := nElements + 7 // 8.
+ 			 instSpec := instSpec + (8 - nElements bitAnd: 7)] }
+ 		otherwise: "non-indexable"
+ 			["Some Squeak images include funky fixed subclasses of abstract variable
+ 			  superclasses. e.g. DirectoryEntry as a subclass of ArrayedCollection.
+ 			  The (Threaded)FFIPlugin expects to be able to instantiate ExternalData via
+ 			  this method.
+ 			  Hence allow fixed classes to be instantiated here iff nElements = 0."
+ 			 (nElements ~= 0 or: [instSpec > self lastPointerFormat]) ifTrue:
+ 				[^nil].
+ 			 numSlots := self fixedFieldsOfClassFormat: classFormat.
+ 			 fillValue := nilObj].
+ 	classIndex = 0 ifTrue:
+ 		[classIndex := self ensureBehaviorHash: classObj.
+ 		 classIndex < 0 ifTrue:
+ 			[coInterpreter primitiveFailFor: classIndex negated.
+ 			 ^nil]].
+ 	numSlots > self maxSlotsForAlloc ifTrue:
+ 			[coInterpreter primitiveFailFor: PrimErrUnsupported.
+ 			 ^nil].
+ 	newObj := self 
+ 					allocateSlotsForPinningInOldSpace: numSlots 
+ 					bytes: (self objectBytesForSlots: numSlots) 
+ 					format: instSpec 
+ 					classIndex: classIndex.
+ 	newObj ifNotNil:
+ 		[self fillObj: newObj numSlots: numSlots with: fillValue].
+ 	^newObj!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>instantiateUninitializedClass:indexableSize: (in category 'instantiation') -----
+ instantiateUninitializedClass: classObj indexableSize: nElements
+ 	<api>
+ 	<var: #nElements type: #usqInt>
+ 	"Allocate an instance of a variable class, excepting CompiledMethod."
+ 	| instSpec classFormat numSlots classIndex newObj fillValue |
+ 	classFormat := self formatOfClass: classObj.
+ 	instSpec := self instSpecOfClassFormat: classFormat.
+ 	classIndex := self rawHashBitsOf: classObj.
+ 	fillValue := 0.
+ 	self assert: (self isPureBitsFormat: instSpec).
+ 	instSpec caseOf: {
+ 		[self sixtyFourBitIndexableFormat]	->
+ 			[numSlots := nElements].
+ 		[self firstLongFormat]	->
+ 			[(classIndex = ClassFloatCompactIndex and: [nElements ~= 2]) ifTrue:
+ 				[coInterpreter primitiveFailFor: PrimErrBadReceiver.
+ 				 ^nil].
+ 			 numSlots := nElements + 1 // 2.
+ 			 instSpec := instSpec + (nElements bitAnd: 1)].
+ 		[self firstShortFormat]	->
+ 			[numSlots := nElements + 3 // 4.
+ 			 instSpec := instSpec + (4 - nElements bitAnd: 3)].
+ 		[self firstByteFormat]	->
+ 			[numSlots := nElements + 7 // 8.
+ 			 instSpec := instSpec + (8 - nElements bitAnd: 7)] }
+ 		otherwise: "non-indexable"
+ 			["Some Squeak images include funky fixed subclasses of abstract variable
+ 			  superclasses. e.g. DirectoryEntry as a subclass of ArrayedCollection.
+ 			  The (Threaded)FFIPlugin expects to be able to instantiate ExternalData via
+ 			  this method.
+ 			  Hence allow fixed classes to be instantiated here iff nElements = 0."
+ 			 (nElements ~= 0 or: [instSpec > self lastPointerFormat]) ifTrue:
+ 				[^nil].
+ 			 numSlots := self fixedFieldsOfClassFormat: classFormat.
+ 			 fillValue := nilObj].
+ 	classIndex = 0 ifTrue:
+ 		[classIndex := self ensureBehaviorHash: classObj.
+ 		 classIndex < 0 ifTrue:
+ 			[coInterpreter primitiveFailFor: classIndex negated.
+ 			 ^nil]].
+ 	numSlots > self maxSlotsForNewSpaceAlloc
+ 		ifTrue:
+ 			[numSlots > self maxSlotsForAlloc ifTrue:
+ 				[coInterpreter primitiveFailFor: PrimErrUnsupported.
+ 				 ^nil].
+ 			 newObj := self allocateSlotsInOldSpace: numSlots format: instSpec classIndex: classIndex]
+ 		ifFalse:
+ 			[newObj := self allocateSlots: numSlots format: instSpec classIndex: classIndex].
+ 	^newObj!

Item was added:
+ ----- Method: SpurMemoryManager>>inOldSpaceInstantiatePinnedClass: (in category 'allocation') -----
+ inOldSpaceInstantiatePinnedClass: classObj
+ 	| instSpec classFormat numSlots classIndex newObj |
+ 	classFormat := self formatOfClass: classObj.
+ 	instSpec := self instSpecOfClassFormat: classFormat.
+ 	(self isFixedSizePointerFormat: instSpec) ifFalse:
+ 		[^nil].
+ 	classIndex := self ensureBehaviorHash: classObj.
+ 	classIndex < 0 ifTrue:
+ 		[coInterpreter primitiveFailFor: classIndex negated.
+ 		 ^nil].
+ 	numSlots := self fixedFieldsOfClassFormat: classFormat.
+ 	newObj := self 
+ 				allocateSlotsForPinningInOldSpace: numSlots 
+ 				bytes: (self objectBytesForSlots: numSlots) 
+ 				format: instSpec 
+ 				classIndex: classIndex.
+ 	newObj ifNotNil:
+ 		[self fillObj: newObj numSlots: numSlots with: nilObj].
+ 	^newObj!

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

Item was changed:
  ----- Method: VMClass class>>openSpurMultiWindowBrowser (in category 'utilities') -----
  openSpurMultiWindowBrowser
  	"Answer a new multi-window browser on the Spur classes, the Cog StackInterpreter classes, and the support classes"
+ 	"self openSpurMultiWindowBrowser"
  	| b |
  	b := Browser open.
  	#(	SpurMemoryManager Spur32BitMemoryManager Spur64BitMemoryManager
  		SpurGenerationScavenger SpurSegmentManager
  		Spur32BitMMLESimulator SpurGenerationScavengerSimulator
  		InterpreterPrimitives StackInterpreter StackInterpreterPrimitives
  		VMStructType VMMaker CCodeGenerator TMethod)
  		do: [:className|
  			(Smalltalk classNamed: className) ifNotNil:
  				[:class| b selectCategoryForClass: class; selectClass: class]]
  		separatedBy:
  			[b multiWindowState addNewWindow].
  	b multiWindowState selectWindowIndex: 1!

Item was changed:
  ----- Method: VMProfileMacSupportPlugin>>primitiveExecutableModulesAndOffsets (in category 'primitives') -----
  primitiveExecutableModulesAndOffsets
  	"Answer an Array of quads for executable modules (the VM executable
  	 and loaded libraries).  Each quad is the module's name, its vm address
  	 relocation in memory, the (unrelocated) start address, and the size."
  	| nimages resultObj name valueObj nameObjData slide start size |
  	<export: true>
  	<var: #name type: 'const char *'>
  	<var: #nameObjData type: #'char *'>
  	<var: #h type: 'const struct mach_header *'>
  	<var: #h64 type: 'const struct mach_header_64 *'>
  	<var: #s64 type: 'const struct section_64 *'>
  	<var: #s type: 'const struct section *'>
  	<var: #start type: 'usqIntptr_t'>
  	<var: #slide type: 'usqIntptr_t'>
  	<var: #size type: 'usqIntptr_t'>
  	self cppIf: #'MAC_OS_X_VERSION_MIN_REQUIRED' <= #'MAC_OS_X_VERSION_10_4'
  		ifTrue: "_dyld_present was deprecated in 10.5"
  			[(self cCode: '_dyld_present()' inSmalltalk: false) ifFalse:
  				[^interpreterProxy primitiveFail]].
  	nimages := self cCode: '_dyld_image_count()' inSmalltalk: 0.
  	resultObj := interpreterProxy instantiateClass: interpreterProxy classArray indexableSize: nimages * 4.
  	resultObj = 0 ifTrue:
  		[^interpreterProxy primitiveFail].
  
  	interpreterProxy pushRemappableOop: resultObj.
  	0 to: nimages - 1 do:
  		[:i|
  		start := size := -1. "impossible start & size"
  		name := self cCode: '_dyld_get_image_name(i)' inSmalltalk: 0.
  		slide   := self cCode: '_dyld_get_image_vmaddr_slide(i)' inSmalltalk: 0.
+ 		self cppIf: #'__x86_64__' | #'__arm64__'
- 		self cppIf: #'__x86_64__'
  			ifTrue:
  				[(self cCode: '(const struct mach_header_64 *)_dyld_get_image_header(i)' inSmalltalk: nil) ifNotNil:
  					[:h64|
  					 (self cCode: 'getsectbynamefromheader_64(h64,SEG_TEXT,SECT_TEXT)' inSmalltalk: nil) ifNotNil:
  						[:s64|
  						 start := self cCode: 's64->addr' inSmalltalk: 0.
  						 size := self cCode: 's64->size' inSmalltalk: 0]]]
  			ifFalse:
  				[(self cCode: '_dyld_get_image_header(i)' inSmalltalk: nil) ifNotNil:
  					[:h|
  					 (self cCode: 'getsectbynamefromheader(h,SEG_TEXT,SECT_TEXT)' inSmalltalk: nil) ifNotNil:
  						[:s|
  						 start := self cCode: 's->addr' inSmalltalk: 0.
  						 size := self cCode: 's->size' inSmalltalk: 0]]].
  
  		valueObj := interpreterProxy
  						instantiateClass: interpreterProxy classString
  						indexableSize: (self strlen: name).
  		interpreterProxy failed ifTrue:
  			[interpreterProxy popRemappableOop.
  			 ^interpreterProxy primitiveFail].
  		interpreterProxy storePointer: i * 4 ofObject: interpreterProxy topRemappableOop withValue: valueObj.
  		nameObjData := interpreterProxy arrayValueOf: valueObj.
  		self memcpy: nameObjData _: name _: (self strlen: name).
  
  		valueObj := interpreterProxy signedMachineIntegerFor: slide.
  		interpreterProxy failed ifTrue:
  			[interpreterProxy popRemappableOop.
  			 ^interpreterProxy primitiveFail].
  		interpreterProxy storePointer: i * 4 + 1 ofObject: interpreterProxy topRemappableOop withValue: valueObj.
  
  		valueObj := interpreterProxy positiveMachineIntegerFor: start.
  		interpreterProxy failed ifTrue:
  			[interpreterProxy popRemappableOop.
  			 ^interpreterProxy primitiveFail].
  		interpreterProxy storePointer: i * 4 + 2 ofObject: interpreterProxy topRemappableOop withValue: valueObj.
  
  		valueObj := interpreterProxy positiveMachineIntegerFor: size.
  		interpreterProxy failed ifTrue:
  			[interpreterProxy popRemappableOop.
  			 ^interpreterProxy primitiveFail].
  		interpreterProxy storePointer: i * 4 + 3 ofObject: interpreterProxy topRemappableOop withValue: valueObj].
  
  	resultObj := interpreterProxy popRemappableOop.
  	^interpreterProxy pop: 1 thenPush: resultObj!




More information about the Vm-dev mailing list