<div dir="ltr"><div class="gmail_default" style="font-size:small">Hi All,<br></div><div class="gmail_default" style="font-size:small"><br></div><div class="gmail_default" style="font-size:small">    I'd like to thank Tom Braun who is now working on the VM! Tom has contributed pinned new and uninitialized new and is working on the incremental GC.</div></div><br><div class="gmail_quote"><div dir="ltr" class="gmail_attr">On Tue, Jun 21, 2022 at 10:23 AM <<a href="mailto:commits@source.squeak.org">commits@source.squeak.org</a>> wrote:<br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left-width:1px;border-left-style:solid;border-left-color:rgb(204,204,204);padding-left:1ex"> <br>
Tom Braun uploaded a new version of VMMaker to project VM Maker:<br>
<a href="http://source.squeak.org/VMMaker/VMMaker.oscog-WoC.3195.mcz" rel="noreferrer" target="_blank">http://source.squeak.org/VMMaker/VMMaker.oscog-WoC.3195.mcz</a><br>
<br>
==================== Summary ====================<br>
<br>
Name: VMMaker.oscog-WoC.3195<br>
Author: WoC<br>
Time: 21 June 2022, 7:15:36.142009 pm<br>
UUID: 2e2c7dd0-3800-4463-ae4f-a62c68245333<br>
Ancestors: VMMaker.oscog-eem.3194<br>
<br>
adding pinning primitives (instantiate a pinned object in old space avoiding the overhead of allocating it in new space + become)<br>
adding uninitialized new primitives for 64 bits Spur (including lifting the single header word limitation in the jit)<br>
fix printing of CogAbstractInstruction<br>
fixed comments in 64 bit Spur newWithArg jit<br>
attempt to fix the mac profile plugin for 64 bit arm<br>
<br>
=============== Diff against VMMaker.oscog-eem.3194 ===============<br>
<br>
Item was added:<br>
+ ----- Method: CogAbstractInstruction class>>registerMaskFor:and:and:and:and:and:and:and:and:and:and:and: (in category 'register management') -----<br>
+ registerMaskFor: reg1 and: reg2 and: reg3 and: reg4 and: reg5 and: reg6 and: reg7 and: reg8 and: reg9 and: reg10 and: reg11 and: reg12<br>
+       ^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!<br>
<br>
Item was added:<br>
+ ----- Method: CogAbstractInstruction class>>registerMaskFor:and:and:and:and:and:and:and:and:and:and:and:and:and:and: (in category 'register management') -----<br>
+ 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<br>
+       ^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!<br>
<br>
Item was changed:<br>
  ----- Method: CogAbstractInstruction>>printStateOn: (in category 'printing') -----<br>
  printStateOn: aStream<br>
        | opcodeName orneryOperands format |<br>
        <doNotGenerate> "Smalltalk-side only"<br>
        opcode ifNil:<br>
                [^self].<br>
        aStream space; nextPut: $(; nextPutAll: (opcodeName := self class nameForOpcode: opcode).<br>
        orneryOperands := operands isCObjectAccessor<br>
                                                        ifTrue: [operands object]<br>
                                                        ifFalse: [operands].<br>
        format := ((CogRTLOpcodes classPool includesKey: opcodeName)<br>
                                ifTrue: [CogRTLOpcodes]<br>
                                ifFalse: [self class]) printFormatForOpcodeName: opcodeName.<br>
+       (format ifNil: [orneryOperands] ifNotNil: [orneryOperands first: (format size min: orneryOperands size)]) withIndexDo:<br>
-       (format ifNil: [orneryOperands] ifNotNil: [orneryOperands first: format size]) withIndexDo:<br>
                [:operand :index|<br>
                operand ifNotNil:<br>
                        [aStream space.<br>
                         index >= (orneryOperands identityIndexOf: nil ifAbsent: [orneryOperands size + 1]) ifTrue:<br>
                                [aStream print: index - 1; nextPut: $:].<br>
                         (format notNil and: ['rf' includes: (format at: index ifAbsent: $-)])<br>
                                ifTrue: [aStream nextPutAll: ((format at: index) = $r<br>
                                                                                                ifTrue: [self nameForRegister: operand]<br>
                                                                                                ifFalse: [self nameForFPRegister: operand])]<br>
                                ifFalse:<br>
                                        [| operandNameOrNil |<br>
                                         operandNameOrNil := operand isInteger ifTrue:<br>
                                                                                                [(cogit coInterpreter lookupAddress: operand) ifNil:<br>
                                                                                                        [objectMemory lookupAddress: operand]].<br>
                                         operandNameOrNil ifNotNil: [aStream nextPut: ${].<br>
                                         aStream print: operand.<br>
                                         (operand isInteger and: [operand > 16 and: [opcode ~= Label]]) ifTrue:<br>
                                                [objectMemory wordSize = 8<br>
                                                        ifTrue:<br>
                                                                [(operand allMask: 1 << 63) ifTrue:<br>
                                                                        [aStream nextPut: $/; print: operand signedIntFromLong64]]<br>
                                                        ifFalse:<br>
                                                                [(operand allMask: 1 << 31) ifTrue:<br>
                                                                        [aStream nextPut: $/; print: operand signedIntFromLong]].<br>
                                                 aStream nextPut: $/.<br>
                                                 operand printOn: aStream base: 16.<br>
                                                 operandNameOrNil ifNotNil:<br>
                                                        [aStream nextPut: $=; nextPutAll: operandNameOrNil; nextPut: $}]]]]].<br>
        machineCodeSize ifNotNil:<br>
                [(machineCodeSize between: 1 and: machineCode size) ifTrue:<br>
                        [0 to: machineCodeSize - 1 by: self codeGranularity do:<br>
                                [:i|<br>
                                 aStream space.<br>
                                 (self machineCodeAt: i)<br>
                                        ifNil: [aStream nextPut: $.]<br>
                                        ifNotNil:<br>
                                                [:mc|<br>
                                                mc isInteger<br>
                                                        ifTrue: [mc printOn: aStream base: 16]<br>
                                                        ifFalse: [mc printOn: aStream]]]]].<br>
        address ifNotNil:<br>
                [aStream space; nextPut: $@.<br>
                 address printOn: aStream base: 16].<br>
        aStream nextPut: $)!<br>
<br>
Item was added:<br>
+ ----- Method: CogObjectRepresentation>>genPrimitiveUninitializedNewWithArg (in category 'primitive generators') -----<br>
+ genPrimitiveUninitializedNewWithArg<br>
+       "subclasses override if they can"<br>
+       ^UnimplementedPrimitive!<br>
<br>
Item was changed:<br>
  ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveNewWithArg (in category 'primitive generators') -----<br>
  genPrimitiveNewWithArg<br>
        "Implement primitiveNewWithArg for convenient cases:<br>
        - the receiver has a hash<br>
        - the receiver is variable and not compiled method<br>
        - single word header/num slots < numSlotsMask<br>
        - the result fits in eden<br>
        See superclass method for dynamic frequencies of formats.<br>
        For the moment we implement only arrayFormat, firstByteFormat & firstLongFormat"<br>
<br>
        | headerReg fillReg instSpecReg byteSizeReg maxSlots<br>
          jumpArrayTooBig jumpByteTooBig jumpLongTooBig<br>
          jumpArrayFormat jumpByteFormat jumpBytePrepDone jumpLongPrepDone<br>
          jumpUnhashed jumpNElementsNonInt jumpFailCuzFixed jumpNoSpace jumpHasSlots fillLoop skip |<br>
-       <var: 'skip' type: #'AbstractInstruction *'><br>
-       <var: 'fillLoop' type: #'AbstractInstruction *'>        <br>
-       <var: 'jumpHasSlots' type: #'AbstractInstruction *'><br>
-       <var: 'jumpNoSpace' type: #'AbstractInstruction *'><br>
-       <var: 'jumpUnhashed' type: #'AbstractInstruction *'><br>
-       <var: 'jumpByteFormat' type: #'AbstractInstruction *'><br>
-       <var: 'jumpByteTooBig' type: #'AbstractInstruction *'><br>
-       <var: 'jumpLongTooBig' type: #'AbstractInstruction *'><br>
-       <var: 'jumpArrayFormat' type: #'AbstractInstruction *'><br>
-       <var: 'jumpArrayTooBig' type: #'AbstractInstruction *'><br>
-       <var: 'jumpFailCuzFixed' type: #'AbstractInstruction *'><br>
-       <var: 'jumpBytePrepDone' type: #'AbstractInstruction *'><br>
-       <var: 'jumpLongPrepDone' type: #'AbstractInstruction *'><br>
-       <var: 'jumpNElementsNonInt' type: #'AbstractInstruction *'><br>
<br>
        NewspeakVM ifTrue:<br>
                [cogit methodNumArgs = 2 ifTrue:<br>
                        [^self genPrimitiveMirrorNewWithArg]].<br>
        cogit methodNumArgs ~= 1 ifTrue:<br>
                [^UnimplementedPrimitive].<br>
        cogit genLoadArgAtDepth: 0 into: Arg0Reg.<br>
<br>
        "header will contain classIndex/class's hash & format & numSlots/fixed size"<br>
        headerReg := SendNumArgsReg.<br>
        "Assume there's an available scratch register on 64-bit machines.  This holds the saved numFixedFields and then the value to fill with"<br>
        fillReg := Extra0Reg.<br>
        self assert: fillReg > 0.<br>
        "inst spec will hold class's instance specification and then byte size"<br>
        instSpecReg := byteSizeReg := ClassReg.<br>
        "The max slots we'll allocate here are those for a single header"<br>
        maxSlots := objectMemory numSlotsMask - 1.<br>
<br>
        "get freeStart as early as possible so as not to wait later..."<br>
        cogit MoveAw: objectMemory freeStartAddress R: Arg1Reg.<br>
        "get class's hash & fail if 0"<br>
        self genGetHashFieldNonImmOf: ReceiverResultReg into: headerReg.<br>
        jumpUnhashed := cogit JumpZero: 0.<br>
        "get index and fail if not a +ve integer"<br>
        jumpNElementsNonInt := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.<br>
        "get class's format inst var for inst spec (format field)"<br>
        self genLoadSlot: InstanceSpecificationIndex sourceReg: ReceiverResultReg destReg: instSpecReg.<br>
        cogit LogicalShiftRightCq: objectMemory fixedFieldsFieldWidth + self numSmallIntegerTagBits R: instSpecReg.<br>
        cogit AndCq: objectMemory formatMask R: instSpecReg.<br>
        "Add format to classIndex/format header now"<br>
        cogit MoveR: instSpecReg R: TempReg.<br>
        cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.<br>
        cogit AddR: TempReg R: headerReg.<br>
        "get integer value of num fields in fillReg now"<br>
        cogit MoveR: Arg0Reg R: fillReg.<br>
        self genConvertSmallIntegerToIntegerInReg: fillReg.<br>
        "dispatch on format, failing if not variable or if compiled method"<br>
        cogit CmpCq: objectMemory arrayFormat R: instSpecReg.<br>
        jumpArrayFormat := cogit JumpZero: 0.<br>
        cogit CmpCq: objectMemory firstByteFormat R: instSpecReg.<br>
        jumpByteFormat := cogit JumpZero: 0.<br>
        cogit CmpCq: objectMemory firstLongFormat R: instSpecReg.<br>
        jumpFailCuzFixed := cogit JumpNonZero: 0.<br>
<br>
        cogit CmpCq: (objectMemory integerObjectOf: maxSlots * 2) R: Arg0Reg.<br>
        jumpLongTooBig := cogit JumpAbove: 0.<br>
        "save num elements/slot size to instSpecReg"<br>
        cogit MoveR: fillReg R: instSpecReg.<br>
        "compute odd bits and add into headerReg; oddBits := 2 - nElements bitAnd: 1"<br>
        cogit MoveCq: objectMemory wordSize / 4 R: TempReg.<br>
        cogit SubR: instSpecReg R: TempReg.<br>
        cogit AndCq: objectMemory wordSize / 4 - 1 R: TempReg.<br>
        cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.<br>
        cogit AddR: TempReg R: headerReg.<br>
        "round up num elements to numSlots in instSpecReg"<br>
        cogit AddCq: objectMemory wordSize / 4 - 1 R: instSpecReg.<br>
        cogit LogicalShiftRightCq: objectMemory shiftForWord - 2 R: instSpecReg.<br>
        cogit MoveCq: 0 R: fillReg.<br>
        jumpLongPrepDone := cogit Jump: 0. "go allocate"<br>
<br>
        jumpByteFormat jmpTarget:<br>
        (cogit CmpCq: (objectMemory integerObjectOf: maxSlots * objectMemory wordSize) R: Arg0Reg).<br>
        jumpByteTooBig := cogit JumpAbove: 0.<br>
        "save num elements to instSpecReg"<br>
        cogit MoveR: fillReg R: instSpecReg.<br>
+       "compute odd bits and add into headerReg; oddBits := 8 - nElements bitAnd: 7"<br>
-       "compute odd bits and add into headerReg; oddBits := 4 - nElements bitAnd: 3"<br>
        cogit MoveCq: objectMemory wordSize R: TempReg.<br>
        cogit SubR: instSpecReg R: TempReg.<br>
        cogit AndCq: objectMemory wordSize - 1 R: TempReg.<br>
        cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.<br>
        cogit AddR: TempReg R: headerReg.<br>
        "round up num elements to numSlots in instSpecReg"<br>
        cogit AddCq: objectMemory wordSize - 1 R: instSpecReg.<br>
        cogit LogicalShiftRightCq: objectMemory shiftForWord R: instSpecReg.<br>
        cogit MoveCq: 0 R: fillReg.<br>
        jumpBytePrepDone := cogit Jump: 0. "go allocate"<br>
<br>
        jumpArrayFormat jmpTarget:<br>
                (cogit CmpCq: (objectMemory integerObjectOf: maxSlots) R: Arg0Reg).<br>
        jumpArrayTooBig := cogit JumpAbove: 0.<br>
        "save num elements/slot size to instSpecReg"<br>
        cogit MoveR: fillReg R: instSpecReg.<br>
        cogit MoveCq: objectMemory nilObject R: fillReg.<br>
        "fall through to allocate"<br>
<br>
        jumpBytePrepDone jmpTarget:<br>
        (jumpLongPrepDone jmpTarget: cogit Label).<br>
<br>
        "store numSlots to headerReg"<br>
        cogit MoveR: instSpecReg R: TempReg.<br>
        cogit LogicalShiftLeftCq: objectMemory numSlotsFullShift R: TempReg.<br>
        cogit AddR: TempReg R: headerReg.<br>
        "compute byte size; remember 0-sized objects still need 1 slot."<br>
        cogit CmpCq: 0 R: byteSizeReg. "a.k.a. instSpecReg"<br>
        jumpHasSlots := cogit JumpNonZero: 0.<br>
        cogit MoveCq: objectMemory baseHeaderSize * 2 R: byteSizeReg.<br>
        skip := cogit Jump: 0.<br>
        jumpHasSlots jmpTarget:<br>
        (cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: byteSizeReg).<br>
        cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.<br>
        skip jmpTarget:<br>
        "check if allocation fits"<br>
        (cogit AddR: Arg1Reg R: byteSizeReg).<br>
        cogit CmpCq: objectMemory getScavengeThreshold R: byteSizeReg.<br>
        jumpNoSpace := cogit JumpAboveOrEqual: 0.<br>
        "get result, increment freeStart and write it back. Arg1Reg holds new freeStart, the limit of the object"<br>
        cogit MoveR: Arg1Reg R: ReceiverResultReg.<br>
        cogit MoveR: byteSizeReg Aw: objectMemory freeStartAddress.<br>
-       "write other half of header (numSlots/0 identityHash)"<br>
        cogit MoveR: headerReg Mw: 0 r: ReceiverResultReg.<br>
        "now fill"<br>
        cogit LoadEffectiveAddressMw: objectMemory baseHeaderSize r: ReceiverResultReg R: Arg1Reg.<br>
        fillLoop := <br>
        cogit MoveR: fillReg Mw: 0 r: Arg1Reg.<br>
        cogit AddCq: 8 R: Arg1Reg.<br>
        cogit CmpR: Arg1Reg R: byteSizeReg.<br>
        cogit JumpAbove: fillLoop.<br>
        cogit genPrimReturn.<br>
<br>
        jumpNoSpace jmpTarget:<br>
        (jumpUnhashed jmpTarget:<br>
        (jumpFailCuzFixed jmpTarget:<br>
        (jumpArrayTooBig jmpTarget:<br>
        (jumpByteTooBig jmpTarget:<br>
        (jumpLongTooBig jmpTarget:<br>
        (jumpNElementsNonInt jmpTarget: cogit Label)))))).<br>
<br>
        ^0!<br>
<br>
Item was added:<br>
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveUninitializedNewWithArg (in category 'primitive generators') -----<br>
+ genPrimitiveUninitializedNewWithArg<br>
+       "Implement primitiveUninitializedNewWithArg for convenient cases:<br>
+       - the receiver has a hash<br>
+       - the receiver is variable and not compiled method<br>
+       - the result fits in eden<br>
+       See superclass method for dynamic frequencies of formats.<br>
+       For the moment we implement only arrayFormat, firstByteFormat & firstLongFormat"<br>
+ <br>
+       | headerReg fillReg instSpecReg byteSizeReg maxSlots<br>
+         jumpByteTooBig jumpLongTooBig<br>
+         jumpByteFormat jumpLongPrepDone<br>
+         jumpUnhashed jumpNElementsNonInt jumpFailCuzFixed jumpNoSpace jumpHasSlots skip jumpDoubleWordPrepDone jumpDoubleBytePrepDone jumpDoubleByteFormat jumpDoubleWordFormat jumpOverflowHeader jumpNoSpaceBigObjects jumpDoubleWordTooBig jumpShortTooBig |<br>
+ <br>
+       NewspeakVM ifTrue:<br>
+               [cogit methodNumArgs = 2 ifTrue:<br>
+                       [^self genPrimitiveMirrorNewWithArg]].<br>
+       cogit methodNumArgs ~= 1 ifTrue:<br>
+               [^UnimplementedPrimitive].<br>
+       cogit genLoadArgAtDepth: 0 into: Arg0Reg.<br>
+ <br>
+       "header will contain classIndex/class's hash & format & numSlots/fixed size"<br>
+       headerReg := SendNumArgsReg.<br>
+       "Assume there's an available scratch register on 64-bit machines.  This holds the saved numFixedFields and then the value to fill with"<br>
+       fillReg := Extra0Reg.<br>
+       self assert: fillReg > 0.<br>
+       "inst spec will hold class's instance specification and then byte size"<br>
+       instSpecReg := byteSizeReg := ClassReg.<br>
+       "Allow a max of 1 MB"<br>
+       maxSlots := objectMemory maxSlotsForNewSpaceAlloc.<br>
+ <br>
+       "get freeStart as early as possible so as not to wait later..."<br>
+       cogit MoveAw: objectMemory freeStartAddress R: Arg1Reg.<br>
+       "get class's hash & fail if 0"<br>
+       self genGetHashFieldNonImmOf: ReceiverResultReg into: headerReg.<br>
+       jumpUnhashed := cogit JumpZero: 0.<br>
+       "get index and fail if not a +ve integer"<br>
+       jumpNElementsNonInt := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.<br>
+       "get class's format inst var for inst spec (format field)"<br>
+       self genLoadSlot: InstanceSpecificationIndex sourceReg: ReceiverResultReg destReg: instSpecReg.<br>
+       cogit LogicalShiftRightCq: objectMemory fixedFieldsFieldWidth + self numSmallIntegerTagBits R: instSpecReg.<br>
+       cogit AndCq: objectMemory formatMask R: instSpecReg.<br>
+       "Add format to classIndex/format header now"<br>
+       cogit MoveR: instSpecReg R: TempReg.<br>
+       cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.<br>
+       cogit AddR: TempReg R: headerReg.<br>
+       "get integer value of num fields in fillReg now"<br>
+       cogit MoveR: Arg0Reg R: fillReg.<br>
+       self genConvertSmallIntegerToIntegerInReg: fillReg.<br>
+       "dispatch on format, failing if not a byte format"<br>
+       cogit CmpCq: objectMemory firstByteFormat R: instSpecReg.<br>
+       jumpByteFormat := cogit JumpZero: 0.<br>
+       cogit CmpCq: objectMemory firstShortFormat R: instSpecReg.<br>
+       jumpDoubleByteFormat := cogit JumpZero: 0.<br>
+       cogit CmpCq: objectMemory sixtyFourBitIndexableFormat R: instSpecReg.<br>
+       jumpDoubleWordFormat := cogit JumpZero: 0.<br>
+       cogit CmpCq: objectMemory firstLongFormat R: instSpecReg.<br>
+       jumpFailCuzFixed := cogit JumpNonZero: 0.<br>
+ <br>
+       "allocates a 32-bit array"<br>
+       cogit CmpCq: (objectMemory integerObjectOf: maxSlots * 2) R: Arg0Reg.<br>
+       jumpLongTooBig := cogit JumpAbove: 0.<br>
+       "save num elements/slot size to instSpecReg"<br>
+       cogit MoveR: fillReg R: instSpecReg.<br>
+       "compute odd bits and add into headerReg; oddBits := 2 - nElements bitAnd: 1"<br>
+       cogit MoveCq: objectMemory wordSize / 4 R: TempReg.<br>
+       cogit SubR: instSpecReg R: TempReg.<br>
+       cogit AndCq: objectMemory wordSize / 4 - 1 R: TempReg.<br>
+       cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.<br>
+       cogit AddR: TempReg R: headerReg.<br>
+       "round up num elements to numSlots in instSpecReg; (numElements / 2) ceiling"<br>
+       cogit AddCq: objectMemory wordSize / 4 - 1 R: instSpecReg.<br>
+       cogit LogicalShiftRightCq: objectMemory shiftForWord - 2 R: instSpecReg.<br>
+       jumpLongPrepDone := cogit Jump: 0. "go allocate"<br>
+       <br>
+       "allocates a 16-bit array"<br>
+       jumpDoubleByteFormat jmpTarget:<br>
+       (cogit CmpCq: (objectMemory integerObjectOf: maxSlots * 4) R: Arg0Reg).<br>
+       jumpShortTooBig := cogit JumpAbove: 0.<br>
+       "save num elements to instSpecReg"<br>
+       cogit MoveR: fillReg R: instSpecReg.<br>
+       "compute odd bits and add into headerReg; oddBits := 4 - nElements bitAnd: 3"<br>
+       cogit MoveCq: objectMemory wordSize / 2 R: TempReg.<br>
+       cogit SubR: instSpecReg R: TempReg.<br>
+       cogit AndCq: objectMemory wordSize / 2 - 1 R: TempReg.<br>
+       cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.<br>
+       cogit AddR: TempReg R: headerReg.<br>
+       "round up num elements to numSlots in instSpecReg; (numElements / 4) ceiling"<br>
+       cogit AddCq: objectMemory wordSize / 2 - 1 R: instSpecReg.<br>
+       cogit LogicalShiftRightCq: objectMemory shiftForWord - 1 R: instSpecReg.<br>
+       jumpDoubleBytePrepDone := cogit Jump: 0. "go allocate"<br>
+       <br>
+       "allocates a 64-bit array"<br>
+       jumpDoubleWordFormat jmpTarget:<br>
+       (cogit CmpCq: (objectMemory integerObjectOf: maxSlots) R: Arg0Reg).<br>
+       jumpDoubleWordTooBig := cogit JumpAbove: 0.<br>
+       "save num elements to instSpecReg"<br>
+       cogit MoveR: fillReg R: instSpecReg.<br>
+       jumpDoubleWordPrepDone := cogit Jump: 0. "go allocate"<br>
+ <br>
+       "allocates a byte array"<br>
+       jumpByteFormat jmpTarget:<br>
+       (cogit CmpCq: (objectMemory integerObjectOf: maxSlots * objectMemory wordSize) R: Arg0Reg).<br>
+       jumpByteTooBig := cogit JumpAbove: 0.<br>
+       "save num elements to instSpecReg"<br>
+       cogit MoveR: fillReg R: instSpecReg.<br>
+       "compute odd bits and add into headerReg; oddBits := 8 - nElements bitAnd: 7"<br>
+       cogit MoveCq: objectMemory wordSize R: TempReg.<br>
+       cogit SubR: instSpecReg R: TempReg.<br>
+       cogit AndCq: objectMemory wordSize - 1 R: TempReg.<br>
+       cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.<br>
+       cogit AddR: TempReg R: headerReg.<br>
+       "round up num elements to numSlots in instSpecReg; (numElements / 8) ceiling"<br>
+       cogit AddCq: objectMemory wordSize - 1 R: instSpecReg.<br>
+       cogit LogicalShiftRightCq: objectMemory shiftForWord R: instSpecReg.<br>
+       "fall through to allocate"<br>
+ <br>
+       jumpDoubleWordPrepDone jmpTarget:<br>
+       (jumpDoubleBytePrepDone jmpTarget:<br>
+       (jumpLongPrepDone jmpTarget: cogit Label)).<br>
+ <br>
+       "if numSlots >= 255 -> overflow header -> handle it"<br>
+       cogit CmpCq: objectMemory numSlotsMask R: instSpecReg.<br>
+       jumpOverflowHeader := cogit JumpAboveOrEqual: 0.<br>
+       "fallthrough: allocate objects with < 255 slots"<br>
+       <br>
+       "store numSlots to headerReg"<br>
+       cogit MoveR: instSpecReg R: TempReg.<br>
+       cogit LogicalShiftLeftCq: objectMemory numSlotsFullShift R: TempReg.<br>
+       cogit AddR: TempReg R: headerReg.<br>
+       "compute byte size; remember 0-sized objects still need 1 slot."<br>
+       cogit CmpCq: 0 R: byteSizeReg. "a.k.a. instSpecReg"<br>
+       jumpHasSlots := cogit JumpNonZero: 0.<br>
+       cogit MoveCq: objectMemory baseHeaderSize * 2 R: byteSizeReg.<br>
+       skip := cogit Jump: 0.<br>
+       jumpHasSlots jmpTarget:<br>
+       (cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: byteSizeReg).<br>
+       cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.<br>
+       skip jmpTarget:<br>
+       "check if allocation fits"<br>
+       (cogit AddR: Arg1Reg R: byteSizeReg).<br>
+       cogit CmpCq: objectMemory getScavengeThreshold R: byteSizeReg.<br>
+       jumpNoSpace := cogit JumpAboveOrEqual: 0.<br>
+       "get result, increment freeStart and write it back. Arg1Reg holds new freeStart, the limit of the object"<br>
+       cogit MoveR: Arg1Reg R: ReceiverResultReg.<br>
+       cogit MoveR: byteSizeReg Aw: objectMemory freeStartAddress.<br>
+       "write other half of header (numSlots/0 identityHash)"<br>
+       cogit MoveR: headerReg Mw: 0 r: ReceiverResultReg.<br>
+       cogit genPrimReturn.<br>
+       <br>
+       "allocate object with up to 1 << 16 - 1 slots; numSlots >= 255"<br>
+       "store always 255 to headerReg"<br>
+       jumpOverflowHeader jmpTarget:<br>
+       (cogit MoveCq: 255 R: TempReg).<br>
+       cogit LogicalShiftLeftCq: objectMemory numSlotsFullShift R: TempReg.<br>
+       cogit AddR: TempReg R: headerReg.<br>
+       "calculate overflow header; Temp Reg can be resued as it already contains 255 as needed"<br>
+       cogit AddR: instSpecReg R: TempReg.<br>
+       "compute byte size"<br>
+       cogit AddCq: (objectMemory baseHeaderSize * 2) / objectMemory wordSize R: byteSizeReg.<br>
+       cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.<br>
+       "check if allocation fits"<br>
+       cogit AddR: Arg1Reg R: byteSizeReg.<br>
+       cogit CmpCq: objectMemory getScavengeThreshold R: byteSizeReg.<br>
+       jumpNoSpaceBigObjects := cogit JumpAboveOrEqual: 0.<br>
+       "get result, increment freeStart and write it back. Arg1Reg holds new freeStart, the limit of the object"<br>
+       cogit MoveR: Arg1Reg R: ReceiverResultReg.<br>
+       cogit MoveR: byteSizeReg Aw: objectMemory freeStartAddress.<br>
+       "write overflow part"<br>
+       cogit MoveR: TempReg Mw: 0 r: ReceiverResultReg.<br>
+       "write header"<br>
+       cogit MoveR: headerReg Mw: objectMemory baseHeaderSize r: ReceiverResultReg.<br>
+       cogit genPrimReturn.<br>
+       <br>
+       jumpShortTooBig jmpTarget:<br>
+       (jumpDoubleWordTooBig jmpTarget:<br>
+       (jumpNoSpaceBigObjects jmpTarget:<br>
+       (jumpNoSpace jmpTarget:<br>
+       (jumpUnhashed jmpTarget:<br>
+       (jumpFailCuzFixed jmpTarget:<br>
+       (jumpByteTooBig jmpTarget:<br>
+       (jumpLongTooBig jmpTarget:<br>
+       (jumpNElementsNonInt jmpTarget: cogit Label)))))))).<br>
+ <br>
+       ^0!<br>
<br>
Item was added:<br>
+ ----- Method: Cogit>>registerMaskFor:and:and:and:and:and:and:and:and:and:and:and: (in category 'register management') -----<br>
+ registerMaskFor: reg1 and: reg2 and: reg3 and: reg4 and: reg5 and: reg6 and: reg7 and: reg8 and: reg9 and: reg10  and: reg11 and: reg12<br>
+       <inline: true><br>
+       ^((((((((((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!<br>
<br>
Item was added:<br>
+ ----- Method: Cogit>>registerMaskFor:and:and:and:and:and:and:and:and:and:and:and:and:and:and: (in category 'register management') -----<br>
+ 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<br>
+       <inline: true><br>
+       ^(((((((((((((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!<br>
<br>
Item was added:<br>
+ ----- Method: CurrentImageCoInterpreterFacade>>maxSlotsForNewSpaceAlloc (in category 'accessing') -----<br>
+ maxSlotsForNewSpaceAlloc<br>
+       <br>
+       ^ objectMemory maxSlotsForNewSpaceAlloc!<br>
<br>
Item was added:<br>
+ ----- Method: InterpreterPrimitives>>primitiveNewPinnedInOldSpace (in category 'object access primitives') -----<br>
+ primitiveNewPinnedInOldSpace<br>
+       NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."<br>
+               [(argumentCount < 1<br>
+                 or: [self objCouldBeClassObj: self stackTop]) ifFalse:<br>
+                       [^self primitiveFailFor: PrimErrBadArgument]].<br>
+       objectMemory hasSpurMemoryManagerAPI<br>
+               ifTrue:<br>
+                       ["Allocate a new fixed-size instance.  Fail if the allocation would leave<br>
+                         less than lowSpaceThreshold bytes free. This *will not* cause a GC :-)"<br>
+                       (objectMemory instantiateClass: self stackTop)<br>
+                               ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]<br>
+                               ifNil: [self primitiveFailFor: ((objectMemory isFixedSizePointerFormat: (objectMemory instSpecOfClass: self stackTop))<br>
+                                                                                       ifTrue: [PrimErrNoMemory]<br>
+                                                                                       ifFalse: [PrimErrBadReceiver])]]<br>
+               ifFalse:<br>
+                       ["Allocate a new fixed-size instance. Fail if the allocation would leave<br>
+                         less than lowSpaceThreshold bytes free. May cause a GC."<br>
+                       | spaceOkay |<br>
+                       "The following may cause GC!! Use var for result to permit inlining."<br>
+                       spaceOkay := objectMemory<br>
+                                                               sufficientSpaceToInstantiate: self stackTop<br>
+                                                               indexableSize: 0.<br>
+                       spaceOkay<br>
+                               ifTrue:<br>
+                                       [self<br>
+                                               pop: argumentCount + 1<br>
+                                               thenPush: (objectMemory<br>
+                                                                       instantiateClass: self stackTop<br>
+                                                                       indexableSize: 0)]<br>
+                               ifFalse: [self primitiveFailFor: PrimErrNoMemory]]!<br>
<br>
Item was added:<br>
+ ----- Method: InterpreterPrimitives>>primitiveNewWithArgUninitialized (in category 'object access primitives') -----<br>
+ primitiveNewWithArgUninitialized<br>
+       "Allocate a new indexable instance. Fail if the allocation would leave less than lowSpaceThreshold bytes free. May cause a GC."<br>
+       | size spaceOkay instSpec |<br>
+       NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."<br>
+               [(argumentCount < 2<br>
+                 or: [self addressCouldBeClassObj: (self stackValue: 1)]) ifFalse:<br>
+                       [^self primitiveFailFor: PrimErrBadArgument]].<br>
+       size := self positiveMachineIntegerValueOf: self stackTop.<br>
+       self successful ifFalse:"positiveMachineIntegerValueOf: succeeds only for non-negative integers."<br>
+               [^self primitiveFailFor: PrimErrBadArgument].<br>
+       objectMemory hasSpurMemoryManagerAPI<br>
+               ifTrue:<br>
+                       [(objectMemory instantiateUninitializedClass: (self stackValue: 1) indexableSize: size)<br>
+                               ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]<br>
+                               ifNil: [instSpec := objectMemory instSpecOfClass: (self stackValue: 1).<br>
+                                         self primitiveFailFor: (((objectMemory isIndexableFormat: instSpec)<br>
+                                                                                       and: [(objectMemory isCompiledMethodFormat: instSpec) not])<br>
+                                                                                               ifTrue: [PrimErrNoMemory]<br>
+                                                                                               ifFalse: [PrimErrBadReceiver])]]<br>
+               ifFalse:<br>
+                       [spaceOkay := objectMemory sufficientSpaceToInstantiate: (self stackValue: 1) indexableSize: size.<br>
+                        spaceOkay<br>
+                               ifTrue:<br>
+                                       [self<br>
+                                               pop: argumentCount + 1<br>
+                                               thenPush: (objectMemory instantiateClass: (self stackValue: 1) indexableSize: size)]<br>
+                               ifFalse:<br>
+                                       [self primitiveFailFor: PrimErrNoMemory]]!<br>
<br>
Item was changed:<br>
  ----- Method: SimpleStackBasedCogit class>>initializePrimitiveTableForSqueak (in category 'class initialization') -----<br>
  initializePrimitiveTableForSqueak<br>
        "Initialize the table of primitive generators.  This does not include normal primitives implemented in the coInterpreter.<br>
         N.B. primitives that don't have an explicit arg count (the integer following the generator) may be variadic."<br>
        "SimpleStackBasedCogit initializePrimitiveTableForSqueak"<br>
        MaxCompiledPrimitiveIndex := self objectRepresentationClass wordSize = 8<br>
+                                                                               ifTrue: [580]<br>
+                                                                               ifFalse: [580].<br>
-                                                                               ifTrue: [575]<br>
-                                                                               ifFalse: [575].<br>
        primitiveTable := CArrayAccessor on: (Array new: MaxCompiledPrimitiveIndex + 1).<br>
        self table: primitiveTable from: <br>
        #(      "Integer Primitives (0-19)"<br>
                (1 genPrimitiveAdd                              1)<br>
                (2 genPrimitiveSubtract         1)<br>
                (3 genPrimitiveLessThan         1)<br>
                (4 genPrimitiveGreaterThan              1)<br>
                (5 genPrimitiveLessOrEqual              1)<br>
                (6 genPrimitiveGreaterOrEqual   1)<br>
                (7 genPrimitiveEqual                    1)<br>
                (8 genPrimitiveNotEqual         1)<br>
                (9 genPrimitiveMultiply                 1)<br>
                (10 genPrimitiveDivide                  1)<br>
                (11 genPrimitiveMod                     1)<br>
                (12 genPrimitiveDiv                             1)<br>
                (13 genPrimitiveQuo                     1)<br>
                (14 genPrimitiveBitAnd                  1)<br>
                (15 genPrimitiveBitOr                   1)<br>
                (16 genPrimitiveBitXor                  1)<br>
                (17 genPrimitiveBitShift                1)<br>
                (18 genPrimitiveMakePoint               1)      "this is here mainly to remove noise from printPrimTraceLog()"<br>
                "(19 primitiveFail)"                                    "Guard primitive for simulation -- *must* fail"<br>
<br>
                "LargeInteger Primitives (20-39)"<br>
                "(20 primitiveFail)"<br>
                "(21 primitiveAddLargeIntegers)"<br>
                "(22 primitiveSubtractLargeIntegers)"<br>
                "(23 primitiveLessThanLargeIntegers)"<br>
                "(24 primitiveGreaterThanLargeIntegers)"<br>
                "(25 primitiveLessOrEqualLargeIntegers)"<br>
                "(26 primitiveGreaterOrEqualLargeIntegers)"<br>
                "(27 primitiveEqualLargeIntegers)"<br>
                "(28 primitiveNotEqualLargeIntegers)"<br>
                "(29 primitiveMultiplyLargeIntegers)"<br>
                "(30 primitiveDivideLargeIntegers)"<br>
                "(31 primitiveModLargeIntegers)"<br>
                "(32 primitiveDivLargeIntegers)"<br>
                "(33 primitiveQuoLargeIntegers)"<br>
                "(34 primitiveBitAndLargeIntegers)"<br>
                "(35 primitiveBitOrLargeIntegers)"<br>
                "(36 primitiveBitXorLargeIntegers)"<br>
                "(37 primitiveBitShiftLargeIntegers)"<br>
<br>
                "Float Primitives (38-59)"<br>
                "(38 genPrimitiveFloatAt)"<br>
                "(39 genPrimitiveFloatAtPut)"<br>
                (40 genPrimitiveAsFloat                                 0)<br>
                (41 genPrimitiveFloatAdd                                1)<br>
                (42 genPrimitiveFloatSubtract                   1)<br>
                (43 genPrimitiveFloatLessThan                   1)<br>
                (44 genPrimitiveFloatGreaterThan                1)<br>
                (45 genPrimitiveFloatLessOrEqual                1)<br>
                (46 genPrimitiveFloatGreaterOrEqual     1)<br>
                (47 genPrimitiveFloatEqual                              1)<br>
                (48 genPrimitiveFloatNotEqual                   1)<br>
                (49 genPrimitiveFloatMultiply                   1)<br>
                (50 genPrimitiveFloatDivide                             1)<br>
                "(51 genPrimitiveTruncated)"<br>
                "(52 genPrimitiveFractionalPart)"<br>
                "(53 genPrimitiveExponent)"<br>
                "(54 genPrimitiveTimesTwoPower)"<br>
                (55 genPrimitiveFloatSquareRoot         0)<br>
                "(56 genPrimitiveSine)"<br>
                "(57 genPrimitiveArctan)"<br>
                "(58 genPrimitiveLogN)"<br>
                "(59 genPrimitiveExp)"<br>
<br>
                "Subscript and Stream Primitives (60-67)"<br>
                (60 genPrimitiveAt                              1)<br>
                (61 genPrimitiveAtPut                   2)<br>
                (62 genPrimitiveSize                    0)<br>
                (63 genPrimitiveStringAt                1)<br>
                (64 genPrimitiveStringAtPut     2)<br>
                "The stream primitives no longer pay their way; normal Smalltalk code is faster."<br>
                (65 genFastPrimFail)"was primitiveNext"<br>
                (66 genFastPrimFail) "was primitiveNextPut"<br>
                (67 genFastPrimFail) "was primitiveAtEnd"<br>
<br>
                "StorageManagement Primitives (68-79)"<br>
                (68 genPrimitiveObjectAt                1)      "Good for debugger/InstructionStream performance"<br>
                "(69 primitiveObjectAtPut)"<br>
                (70 genPrimitiveNew                     0)<br>
                (71 genPrimitiveNewWithArg      1)<br>
                "(72 primitiveArrayBecomeOneWay)"               "Blue Book: primitiveBecome"<br>
                "(73 primitiveInstVarAt)"<br>
                "(74 primitiveInstVarAtPut)"<br>
                (75 genPrimitiveIdentityHash    0)<br>
                "(76 primitiveStoreStackp)"                                     "Blue Book: primitiveAsObject"<br>
                "(77 primitiveSomeInstance)"<br>
                "(78 primitiveNextInstance)"<br>
                (79 genPrimitiveNewMethod       2)<br>
<br>
                "Control Primitives (80-89)"<br>
                "(80 primitiveFail)"                                                    "Blue Book: primitiveBlockCopy"<br>
                "(81 primitiveFail)"                                                    "Blue Book: primitiveValue"<br>
                "(82 primitiveFail)"                                                    "Blue Book: primitiveValueWithArgs"<br>
                (83 genPrimitivePerform)<br>
                "(84 primitivePerformWithArgs)"<br>
                "(85 primitiveSignal)"<br>
                "(86 primitiveWait)"<br>
                "(87 primitiveResume)"<br>
                "(88 primitiveSuspend)"<br>
                "(89 primitiveFlushCache)"<br>
<br>
                "(90 primitiveMousePoint)"<br>
                "(91 primitiveTestDisplayDepth)"                        "Blue Book: primitiveCursorLocPut"<br>
                "(92 primitiveSetDisplayMode)"                          "Blue Book: primitiveCursorLink"<br>
                "(93 primitiveInputSemaphore)"<br>
                "(94 primitiveGetNextEvent)"                            "Blue Book: primitiveSampleInterval"<br>
                "(95 primitiveInputWord)"<br>
                "(96 primitiveFail)"    "primitiveCopyBits"<br>
                "(97 primitiveSnapshot)"<br>
                "(98 primitiveStoreImageSegment)"<br>
                "(99 primitiveLoadImageSegment)"<br>
                "(100 primitivePerformInSuperclass)"            "Blue Book: primitiveSignalAtTick"<br>
                "(101 primitiveBeCursor)"<br>
                "(102 primitiveBeDisplay)"<br>
                "(103 primitiveScanCharacters)"<br>
                "(104 primitiveFail)"   "primitiveDrawLoop"<br>
                (105 genPrimitiveStringReplace)<br>
                "(106 primitiveScreenSize)"<br>
                "(107 primitiveMouseButtons)"<br>
                "(108 primitiveKbdNext)"<br>
                "(109 primitiveKbdPeek)"<br>
<br>
<br>
                "System Primitives (110-119)"<br>
                (110 genPrimitiveIdentical 1)<br>
                (111 genPrimitiveClass)                         "Support both class and Context>>objectClass:"<br>
                "(112 primitiveBytesLeft)"<br>
                "(113 primitiveQuit)"<br>
                "(114 primitiveExitToDebugger)"<br>
                "(115 primitiveChangeClass)"                                    "Blue Book: primitiveOopsLeft"<br>
                "(116 primitiveFlushCacheByMethod)"<br>
                "(117 primitiveExternalCall)"<br>
                "(118 primitiveDoPrimitiveWithArgs)"<br>
                "(119 primitiveFlushCacheSelective)"<br>
<br>
                (148 genPrimitiveShallowCopy 0)                 "a.k.a. clone"<br>
<br>
                (158 genPrimitiveStringCompareWith 1)<br>
                (159 genPrimitiveHashMultiply 0)<br>
<br>
                (165 genPrimitiveIntegerAt                      1)      "Signed version of genPrimitiveAt"<br>
                (166 genPrimitiveIntegerAtPut           2)      "Signed version of genPrimitiveAtPut"<br>
<br>
                (169 genPrimitiveNotIdentical 1)<br>
<br>
                (170 genPrimitiveAsCharacter)                           "SmallInteger>>asCharacter, Character class>>value:"<br>
                (171 genPrimitiveImmediateAsInteger 0)  "Character>>asInteger/hash/identityHash, SmallFloat64>>identityHash"<br>
<br>
                (173 genPrimitiveSlotAt 1)                              "Good for micro-benchmark performance, and for reducing noise in Croquet primitive trace logs"<br>
                (174 genPrimitiveSlotAtPut 2)                   "ditto"<br>
                (175 genPrimitiveIdentityHash   0)              "Behavior>>identityHash"<br>
<br>
                "Old closure primitives"<br>
                "(186 primitiveFail)" "was primitiveClosureValue"<br>
                "(187 primitiveFail)" "was primitiveClosureValueWithArgs"<br>
<br>
                "Perform method directly"<br>
                "(188 primitiveExecuteMethodArgsArray)"<br>
                "(189 primitiveExecuteMethod)"<br>
<br>
                "Unwind primitives"<br>
                "(195 primitiveFindNextUnwindContext)"<br>
                "(196 primitiveTerminateTo)"<br>
                "(197 primitiveFindHandlerContext)"<br>
                (198 genFastPrimFail "primitiveMarkUnwindMethod")<br>
                (199 genFastPrimFail "primitiveMarkHandlerMethod")<br>
<br>
                "new closure primitives"<br>
                "(200 primitiveClosureCopyWithCopiedValues)"<br>
                (201 genPrimitiveClosureValue   0) "value"<br>
                (202 genPrimitiveClosureValue   1) "value:"<br>
                (203 genPrimitiveClosureValue   2) "value:value:"<br>
                (204 genPrimitiveClosureValue   3) "value:value:value:"<br>
                (205 genPrimitiveClosureValue   4) "value:value:value:value:"<br>
                "(206 genPrimitiveClosureValueWithArgs)" "valueWithArguments:"<br>
<br>
                (207 genPrimitiveFullClosureValue) "value[:value:value:value:] et al"<br>
                "(208 genPrimitiveFullClosureValueWithArgs)" "valueWithArguments:"<br>
                (209 genPrimitiveFullClosureValue) "valueNoContextSwitch[:value:] et al"<br>
<br>
                "(210 primitiveContextAt)"<br>
                "(211 primitiveContextAtPut)"<br>
                "(212 primitiveContextSize)"<br>
<br>
                "(218 primitiveDoNamedPrimitiveWithArgs)"<br>
                "(219 primitiveFail)"   "reserved for Cog primitives"<br>
<br>
                "(220 primitiveFail)"           "reserved for Cog primitives"<br>
<br>
                (221 genPrimitiveClosureValue   0) "valueNoContextSwitch"<br>
                (222 genPrimitiveClosureValue   1) "valueNoContextSwitch:"<br>
<br>
                "SmallFloat primitives (540-559)"<br>
                (541 genPrimitiveSmallFloatAdd                          1)<br>
                (542 genPrimitiveSmallFloatSubtract                     1)<br>
                (543 genPrimitiveSmallFloatLessThan                     1)<br>
                (544 genPrimitiveSmallFloatGreaterThan          1)<br>
                (545 genPrimitiveSmallFloatLessOrEqual          1)<br>
                (546 genPrimitiveSmallFloatGreaterOrEqual               1)<br>
                (547 genPrimitiveSmallFloatEqual                                1)<br>
                (548 genPrimitiveSmallFloatNotEqual                     1)<br>
                (549 genPrimitiveSmallFloatMultiply                             1)<br>
                (550 genPrimitiveSmallFloatDivide                               1)<br>
                "(551 genPrimitiveSmallFloatTruncated                   0)"<br>
                "(552 genPrimitiveSmallFloatFractionalPart              0)"<br>
                "(553 genPrimitiveSmallFloatExponent                    0)"<br>
                "(554 genPrimitiveSmallFloatTimesTwoPower       1)"<br>
                (555 genPrimitiveSmallFloatSquareRoot                   0)<br>
                "(556 genPrimitiveSmallFloatSine                                0)"<br>
                "(557 genPrimitiveSmallFloatArctan                              0)"<br>
                "(558 genPrimitiveSmallFloatLogN                                0)"<br>
                "(559 genPrimitiveSmallFloatExp                         0)"<br>
                (575 genPrimitiveHighBit                        0)<br>
+               (580 genPrimitiveUninitializedNewWithArg             1)<br>
        )!<br>
<br>
Item was added:<br>
+ ----- Method: Spur64BitMemoryManager>>inOldSpaceInstantiatePinnedClass:indexableSize: (in category 'instantiation') -----<br>
+ inOldSpaceInstantiatePinnedClass: classObj indexableSize: nElements<br>
+       <api><br>
+       <var: #nElements type: #usqInt><br>
+       "Allocate an instance of a variable class, excepting CompiledMethod."<br>
+       | instSpec classFormat numSlots classIndex newObj fillValue |<br>
+       classFormat := self formatOfClass: classObj.<br>
+       instSpec := self instSpecOfClassFormat: classFormat.<br>
+       classIndex := self rawHashBitsOf: classObj.<br>
+       fillValue := 0.<br>
+       instSpec caseOf: {<br>
+               [self arrayFormat]      -><br>
+                       [numSlots := nElements.<br>
+                        fillValue := nilObj].<br>
+               [self indexablePointersFormat]  -><br>
+                       [numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements.<br>
+                        fillValue := nilObj].<br>
+               [self weakArrayFormat]  -><br>
+                       [numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements.<br>
+                        fillValue := nilObj].<br>
+               [self sixtyFourBitIndexableFormat]      -><br>
+                       [numSlots := nElements].<br>
+               [self firstLongFormat]  -><br>
+                       [(classIndex = ClassFloatCompactIndex and: [nElements ~= 2]) ifTrue:<br>
+                               [coInterpreter primitiveFailFor: PrimErrBadReceiver.<br>
+                                ^nil].<br>
+                        numSlots := nElements + 1 // 2.<br>
+                        instSpec := instSpec + (nElements bitAnd: 1)].<br>
+               [self firstShortFormat] -><br>
+                       [numSlots := nElements + 3 // 4.<br>
+                        instSpec := instSpec + (4 - nElements bitAnd: 3)].<br>
+               [self firstByteFormat]  -><br>
+                       [numSlots := nElements + 7 // 8.<br>
+                        instSpec := instSpec + (8 - nElements bitAnd: 7)] }<br>
+               otherwise: "non-indexable"<br>
+                       ["Some Squeak images include funky fixed subclasses of abstract variable<br>
+                         superclasses. e.g. DirectoryEntry as a subclass of ArrayedCollection.<br>
+                         The (Threaded)FFIPlugin expects to be able to instantiate ExternalData via<br>
+                         this method.<br>
+                         Hence allow fixed classes to be instantiated here iff nElements = 0."<br>
+                        (nElements ~= 0 or: [instSpec > self lastPointerFormat]) ifTrue:<br>
+                               [^nil].<br>
+                        numSlots := self fixedFieldsOfClassFormat: classFormat.<br>
+                        fillValue := nilObj].<br>
+       classIndex = 0 ifTrue:<br>
+               [classIndex := self ensureBehaviorHash: classObj.<br>
+                classIndex < 0 ifTrue:<br>
+                       [coInterpreter primitiveFailFor: classIndex negated.<br>
+                        ^nil]].<br>
+       numSlots > self maxSlotsForAlloc ifTrue:<br>
+                       [coInterpreter primitiveFailFor: PrimErrUnsupported.<br>
+                        ^nil].<br>
+       newObj := self <br>
+                                       allocateSlotsForPinningInOldSpace: numSlots <br>
+                                       bytes: (self objectBytesForSlots: numSlots) <br>
+                                       format: instSpec <br>
+                                       classIndex: classIndex.<br>
+       newObj ifNotNil:<br>
+               [self fillObj: newObj numSlots: numSlots with: fillValue].<br>
+       ^newObj!<br>
<br>
Item was added:<br>
+ ----- Method: Spur64BitMemoryManager>>instantiateUninitializedClass:indexableSize: (in category 'instantiation') -----<br>
+ instantiateUninitializedClass: classObj indexableSize: nElements<br>
+       <api><br>
+       <var: #nElements type: #usqInt><br>
+       "Allocate an instance of a variable class, excepting CompiledMethod."<br>
+       | instSpec classFormat numSlots classIndex newObj fillValue |<br>
+       classFormat := self formatOfClass: classObj.<br>
+       instSpec := self instSpecOfClassFormat: classFormat.<br>
+       classIndex := self rawHashBitsOf: classObj.<br>
+       fillValue := 0.<br>
+       self assert: (self isPureBitsFormat: instSpec).<br>
+       instSpec caseOf: {<br>
+               [self sixtyFourBitIndexableFormat]      -><br>
+                       [numSlots := nElements].<br>
+               [self firstLongFormat]  -><br>
+                       [(classIndex = ClassFloatCompactIndex and: [nElements ~= 2]) ifTrue:<br>
+                               [coInterpreter primitiveFailFor: PrimErrBadReceiver.<br>
+                                ^nil].<br>
+                        numSlots := nElements + 1 // 2.<br>
+                        instSpec := instSpec + (nElements bitAnd: 1)].<br>
+               [self firstShortFormat] -><br>
+                       [numSlots := nElements + 3 // 4.<br>
+                        instSpec := instSpec + (4 - nElements bitAnd: 3)].<br>
+               [self firstByteFormat]  -><br>
+                       [numSlots := nElements + 7 // 8.<br>
+                        instSpec := instSpec + (8 - nElements bitAnd: 7)] }<br>
+               otherwise: "non-indexable"<br>
+                       ["Some Squeak images include funky fixed subclasses of abstract variable<br>
+                         superclasses. e.g. DirectoryEntry as a subclass of ArrayedCollection.<br>
+                         The (Threaded)FFIPlugin expects to be able to instantiate ExternalData via<br>
+                         this method.<br>
+                         Hence allow fixed classes to be instantiated here iff nElements = 0."<br>
+                        (nElements ~= 0 or: [instSpec > self lastPointerFormat]) ifTrue:<br>
+                               [^nil].<br>
+                        numSlots := self fixedFieldsOfClassFormat: classFormat.<br>
+                        fillValue := nilObj].<br>
+       classIndex = 0 ifTrue:<br>
+               [classIndex := self ensureBehaviorHash: classObj.<br>
+                classIndex < 0 ifTrue:<br>
+                       [coInterpreter primitiveFailFor: classIndex negated.<br>
+                        ^nil]].<br>
+       numSlots > self maxSlotsForNewSpaceAlloc<br>
+               ifTrue:<br>
+                       [numSlots > self maxSlotsForAlloc ifTrue:<br>
+                               [coInterpreter primitiveFailFor: PrimErrUnsupported.<br>
+                                ^nil].<br>
+                        newObj := self allocateSlotsInOldSpace: numSlots format: instSpec classIndex: classIndex]<br>
+               ifFalse:<br>
+                       [newObj := self allocateSlots: numSlots format: instSpec classIndex: classIndex].<br>
+       ^newObj!<br>
<br>
Item was added:<br>
+ ----- Method: SpurMemoryManager>>inOldSpaceInstantiatePinnedClass: (in category 'allocation') -----<br>
+ inOldSpaceInstantiatePinnedClass: classObj<br>
+       | instSpec classFormat numSlots classIndex newObj |<br>
+       classFormat := self formatOfClass: classObj.<br>
+       instSpec := self instSpecOfClassFormat: classFormat.<br>
+       (self isFixedSizePointerFormat: instSpec) ifFalse:<br>
+               [^nil].<br>
+       classIndex := self ensureBehaviorHash: classObj.<br>
+       classIndex < 0 ifTrue:<br>
+               [coInterpreter primitiveFailFor: classIndex negated.<br>
+                ^nil].<br>
+       numSlots := self fixedFieldsOfClassFormat: classFormat.<br>
+       newObj := self <br>
+                               allocateSlotsForPinningInOldSpace: numSlots <br>
+                               bytes: (self objectBytesForSlots: numSlots) <br>
+                               format: instSpec <br>
+                               classIndex: classIndex.<br>
+       newObj ifNotNil:<br>
+               [self fillObj: newObj numSlots: numSlots with: nilObj].<br>
+       ^newObj!<br>
<br>
Item was changed:<br>
  ----- Method: StackInterpreter class>>initializePrimitiveTable (in category 'initialization') -----<br>
(excessive size, no diff calculated)<br>
<br>
Item was changed:<br>
  ----- Method: VMClass class>>openSpurMultiWindowBrowser (in category 'utilities') -----<br>
  openSpurMultiWindowBrowser<br>
        "Answer a new multi-window browser on the Spur classes, the Cog StackInterpreter classes, and the support classes"<br>
+       "self openSpurMultiWindowBrowser"<br>
        | b |<br>
        b := Browser open.<br>
        #(      SpurMemoryManager Spur32BitMemoryManager Spur64BitMemoryManager<br>
                SpurGenerationScavenger SpurSegmentManager<br>
                Spur32BitMMLESimulator SpurGenerationScavengerSimulator<br>
                InterpreterPrimitives StackInterpreter StackInterpreterPrimitives<br>
                VMStructType VMMaker CCodeGenerator TMethod)<br>
                do: [:className|<br>
                        (Smalltalk classNamed: className) ifNotNil:<br>
                                [:class| b selectCategoryForClass: class; selectClass: class]]<br>
                separatedBy:<br>
                        [b multiWindowState addNewWindow].<br>
        b multiWindowState selectWindowIndex: 1!<br>
<br>
Item was changed:<br>
  ----- Method: VMProfileMacSupportPlugin>>primitiveExecutableModulesAndOffsets (in category 'primitives') -----<br>
  primitiveExecutableModulesAndOffsets<br>
        "Answer an Array of quads for executable modules (the VM executable<br>
         and loaded libraries).  Each quad is the module's name, its vm address<br>
         relocation in memory, the (unrelocated) start address, and the size."<br>
        | nimages resultObj name valueObj nameObjData slide start size |<br>
        <export: true><br>
        <var: #name type: 'const char *'><br>
        <var: #nameObjData type: #'char *'><br>
        <var: #h type: 'const struct mach_header *'><br>
        <var: #h64 type: 'const struct mach_header_64 *'><br>
        <var: #s64 type: 'const struct section_64 *'><br>
        <var: #s type: 'const struct section *'><br>
        <var: #start type: 'usqIntptr_t'><br>
        <var: #slide type: 'usqIntptr_t'><br>
        <var: #size type: 'usqIntptr_t'><br>
        self cppIf: #'MAC_OS_X_VERSION_MIN_REQUIRED' <= #'MAC_OS_X_VERSION_10_4'<br>
                ifTrue: "_dyld_present was deprecated in 10.5"<br>
                        [(self cCode: '_dyld_present()' inSmalltalk: false) ifFalse:<br>
                                [^interpreterProxy primitiveFail]].<br>
        nimages := self cCode: '_dyld_image_count()' inSmalltalk: 0.<br>
        resultObj := interpreterProxy instantiateClass: interpreterProxy classArray indexableSize: nimages * 4.<br>
        resultObj = 0 ifTrue:<br>
                [^interpreterProxy primitiveFail].<br>
<br>
        interpreterProxy pushRemappableOop: resultObj.<br>
        0 to: nimages - 1 do:<br>
                [:i|<br>
                start := size := -1. "impossible start & size"<br>
                name := self cCode: '_dyld_get_image_name(i)' inSmalltalk: 0.<br>
                slide   := self cCode: '_dyld_get_image_vmaddr_slide(i)' inSmalltalk: 0.<br>
+               self cppIf: #'__x86_64__' | #'__arm64__'<br>
-               self cppIf: #'__x86_64__'<br>
                        ifTrue:<br>
                                [(self cCode: '(const struct mach_header_64 *)_dyld_get_image_header(i)' inSmalltalk: nil) ifNotNil:<br>
                                        [:h64|<br>
                                         (self cCode: 'getsectbynamefromheader_64(h64,SEG_TEXT,SECT_TEXT)' inSmalltalk: nil) ifNotNil:<br>
                                                [:s64|<br>
                                                 start := self cCode: 's64->addr' inSmalltalk: 0.<br>
                                                 size := self cCode: 's64->size' inSmalltalk: 0]]]<br>
                        ifFalse:<br>
                                [(self cCode: '_dyld_get_image_header(i)' inSmalltalk: nil) ifNotNil:<br>
                                        [:h|<br>
                                         (self cCode: 'getsectbynamefromheader(h,SEG_TEXT,SECT_TEXT)' inSmalltalk: nil) ifNotNil:<br>
                                                [:s|<br>
                                                 start := self cCode: 's->addr' inSmalltalk: 0.<br>
                                                 size := self cCode: 's->size' inSmalltalk: 0]]].<br>
<br>
                valueObj := interpreterProxy<br>
                                                instantiateClass: interpreterProxy classString<br>
                                                indexableSize: (self strlen: name).<br>
                interpreterProxy failed ifTrue:<br>
                        [interpreterProxy popRemappableOop.<br>
                         ^interpreterProxy primitiveFail].<br>
                interpreterProxy storePointer: i * 4 ofObject: interpreterProxy topRemappableOop withValue: valueObj.<br>
                nameObjData := interpreterProxy arrayValueOf: valueObj.<br>
                self memcpy: nameObjData _: name _: (self strlen: name).<br>
<br>
                valueObj := interpreterProxy signedMachineIntegerFor: slide.<br>
                interpreterProxy failed ifTrue:<br>
                        [interpreterProxy popRemappableOop.<br>
                         ^interpreterProxy primitiveFail].<br>
                interpreterProxy storePointer: i * 4 + 1 ofObject: interpreterProxy topRemappableOop withValue: valueObj.<br>
<br>
                valueObj := interpreterProxy positiveMachineIntegerFor: start.<br>
                interpreterProxy failed ifTrue:<br>
                        [interpreterProxy popRemappableOop.<br>
                         ^interpreterProxy primitiveFail].<br>
                interpreterProxy storePointer: i * 4 + 2 ofObject: interpreterProxy topRemappableOop withValue: valueObj.<br>
<br>
                valueObj := interpreterProxy positiveMachineIntegerFor: size.<br>
                interpreterProxy failed ifTrue:<br>
                        [interpreterProxy popRemappableOop.<br>
                         ^interpreterProxy primitiveFail].<br>
                interpreterProxy storePointer: i * 4 + 3 ofObject: interpreterProxy topRemappableOop withValue: valueObj].<br>
<br>
        resultObj := interpreterProxy popRemappableOop.<br>
        ^interpreterProxy pop: 1 thenPush: resultObj!<br>
<br>
<br>
</blockquote></div><br clear="all"><div><br></div>-- <br><div dir="ltr" class="gmail_signature"><div dir="ltr"><div><span style="font-size:small;border-collapse:separate"><div>_,,,^..^,,,_<br></div><div>best, Eliot</div></span></div></div></div>