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

Eliot Miranda eliot.miranda at gmail.com
Thu Jun 2 09:38:10 UTC 2016


Ben,

> On Jun 1, 2016, at 10:35 PM, Ben Coman <btc at openinworld.com> wrote:
> 
> 
>> On Thu, Jun 2, 2016 at 8:57 AM,  <commits at source.squeak.org> wrote:
>> 
>> Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
>> http://source.squeak.org/VMMaker/VMMaker.oscog-eem.1878.mcz
>> 
>> ==================== Summary ====================
>> 
>> Name: VMMaker.oscog-eem.1878
>> Author: eem
>> Time: 1 June 2016, 5:56:53.625028 pm
>> UUID: 71f5bdb3-74c3-4a8c-bbb9-c78c327e4823
>> Ancestors: VMMaker.oscog-eem.1877
>> 
>> Check for allocation failure in the LargeIntegersPlugin and fail primitives when space runs out.
>> 
>> This is clearly unsatisfactory;. the ciode fails to slow Smalltalk code.  We'd like to run the GC but Spur's style is not to GC in primitives.
> 
> Hi Eliot,
> 
> Does "not to GC *in* primitives" mean from the Image's or VM's perspective?
> 
> Naively I wonder if your approach to primitives failing due to forwarders
> would apply here.  If the primitive runs out of space, set a flag
> before failing,
> and at the same point you test and resolve forwarders, then retry the primitive,
> you could check for this flag, run a GC (outside of the primitive from
> the VM's perspective?),
> then retry the primitive ??

that...is an excellent idea! Beautiful and very easy to implement.  The primitive error code can be tested and if it is PrimErrNoMemory the check-for-failure handler can run the GC before retrying.  I shall implement this tomorrow.  Thanks /very/ much.
 
> cheers -ben
> 
>> If we change the plugin to do GC in primitives we lose the speed advantage of the no-GC style of code.  One approach might be to estimate the memory needed as early as possible, and run a GC if not enough memory is available for the result, recomputing base pointers if GC is run.  This would avoid the awful remapOop:in: style whioch is pessimistic; it puts things in a stack and takes them back out whether a GC is needed or not.  We shoudl use an optimistic algorithm; especially for something as performance sensitive as large integer arithmetic.
>> 
>> =============== Diff against VMMaker.oscog-eem.1877 ===============
>> 
>> Item was changed:
>>  ----- Method: LargeIntegersPlugin>>digit:Lshift: (in category 'oop functions') -----
>>  digit: anOop Lshift: shiftCount
>>        "Attention: this method invalidates all oop's!! Only newOop is valid at return."
>>        "Does not normalize."
>>        | newOop highBit newDigitLen newByteLen oldDigitLen |
>>        oldDigitLen := self digitSizeOfLargeInt: anOop.
>>        (highBit := self cDigitHighBit: (self pointerToFirstDigitOfLargeInt: anOop)
>>                                len: oldDigitLen) = 0 ifTrue: [^  interpreterProxy instantiateClass: (interpreterProxy fetchClassOf: anOop) indexableSize: 1].
>>        newByteLen := highBit + shiftCount + 7 // 8.
>> +       self remapOop: anOop in:
>> +               [newOop := interpreterProxy
>> +                                               instantiateClass: (interpreterProxy fetchClassOf: anOop)
>> +                                               indexableSize: newByteLen].
>> +       newOop ifNil: [^interpreterProxy primitiveFailFor: PrimErrNoMemory].
>> -       self remapOop: anOop in: [newOop := interpreterProxy instantiateClass: (interpreterProxy fetchClassOf: anOop)
>> -                                       indexableSize: newByteLen].
>>        newDigitLen := newByteLen + 3 // 4.
>>        self
>>                cDigitLshift: shiftCount
>>                from: (self pointerToFirstDigitOfLargeInt: anOop)
>>                len: oldDigitLen
>>                to: (self pointerToFirstDigitOfLargeInt: newOop)
>>                len: newDigitLen.
>>        ^ newOop!
>> 
>> Item was changed:
>>  ----- Method: LargeIntegersPlugin>>digit:Rshift:lookfirst: (in category 'oop functions') -----
>>  digit: anOop Rshift: shiftCount lookfirst: a
>>        "Attention: this method invalidates all oop's!! Only newBytes is valid at return."
>>        "Shift right 32*digitShift+bitShift bits, 0<=bitShift<32.
>>        Discard all digits beyond a, and all zeroes at or below a."
>>        "Does not normalize."
>>        | newByteLen newOop oldBitLen newBitLen oldDigitLen newDigitLen |
>>        oldBitLen := self cDigitHighBit: (self pointerToFirstDigitOfLargeInt: anOop) len: a.
>>        oldDigitLen := oldBitLen + 31 // 32.
>>        newBitLen := oldBitLen - shiftCount.
>>        newBitLen <= 0 ifTrue: ["All bits lost"
>>                ^ interpreterProxy
>>                        instantiateClass: (interpreterProxy fetchClassOf: anOop)
>>                        indexableSize: 0].
>>        newByteLen := newBitLen + 7 // 8.
>>        newDigitLen := newByteLen + 3 // 4.
>> +       self remapOop: anOop in:
>> +               [newOop := interpreterProxy
>> +                                               instantiateClass: (interpreterProxy fetchClassOf: anOop)
>> +                                               indexableSize: newByteLen].
>> +       newOop ifNil: [^interpreterProxy primitiveFailFor: PrimErrNoMemory].
>> -       self remapOop: anOop in: [newOop := interpreterProxy instantiateClass: (interpreterProxy fetchClassOf: anOop)
>> -                                       indexableSize: newByteLen].
>>        self
>>                cDigitRshift: shiftCount
>>                from: (self pointerToFirstDigitOfLargeInt: anOop)
>>                len: oldDigitLen
>>                to: (self pointerToFirstDigitOfLargeInt: newOop)
>>                len: newDigitLen.
>>        ^ newOop!
>> 
>> Item was changed:
>>  ----- Method: LargeIntegersPlugin>>digitAddLarge:with: (in category 'oop functions') -----
>>  digitAddLarge: firstInteger with: secondInteger
>>        "Does not need to normalize!!"
>>        | over firstDigitLen secondDigitLen shortInt shortDigitLen longInt longDigitLen sum newSum neg |
>>        <var: #over type: #'unsigned int'>
>>        firstDigitLen := self digitSizeOfLargeInt: firstInteger.
>>        secondDigitLen := self digitSizeOfLargeInt: secondInteger.
>>        neg := interpreterProxy isLargeNegativeIntegerObject: firstInteger.
>>        firstDigitLen <= secondDigitLen
>>                ifTrue:
>>                        [shortInt := firstInteger.
>>                        shortDigitLen := firstDigitLen.
>>                        longInt := secondInteger.
>>                        longDigitLen := secondDigitLen]
>>                ifFalse:
>>                        [shortInt := secondInteger.
>>                        shortDigitLen := secondDigitLen.
>>                        longInt := firstInteger.
>>                        longDigitLen := firstDigitLen].
>>        "       sum := Integer new: len neg: firstInteger negative."
>>        self remapOop: #(shortInt longInt ) in: [sum := self createLargeIntegerNeg: neg digitLength: longDigitLen].
>> +       sum ifNil: [^interpreterProxy primitiveFailFor: PrimErrNoMemory].
>>        over := self
>>                                cDigitAdd: (self pointerToFirstDigitOfLargeInt: shortInt)
>>                                len: shortDigitLen
>>                                with: (self pointerToFirstDigitOfLargeInt: longInt)
>>                                len: longDigitLen
>>                                into: (self pointerToFirstDigitOfLargeInt: sum).
>>        over > 0
>>                ifTrue:
>>                        ["sum := sum growby: 1."
>>                        self remapOop: sum in: [newSum := self createLargeIntegerNeg: neg byteLength: longDigitLen * 4 + 1].
>> +                       newSum ifNil: [^interpreterProxy primitiveFailFor: PrimErrNoMemory].
>>                        self
>>                                cDigitCopyFrom: (self pointerToFirstDigitOfLargeInt: sum)
>>                                to: (self pointerToFirstDigitOfLargeInt: newSum)
>>                                len: longDigitLen.
>>                        sum := newSum.
>>                        "C index!!"
>>                        self cDigitOf: (self pointerToFirstDigitOfLargeInt: sum)
>>                                at: longDigitLen put: over]
>>                ifFalse:
>>                        [sum := neg
>>                                ifTrue: [self normalizeNegative: sum]
>>                                ifFalse: [self normalizePositive: sum]].
>>        ^ sum!
>> 
>> Item was changed:
>>  ----- Method: LargeIntegersPlugin>>digitBitLogic:with:opIndex: (in category 'oop functions') -----
>>  digitBitLogic: firstInteger with: secondInteger opIndex: opIx
>>        "Bit logic here is only implemented for positive integers or Zero;
>>        if rec or arg is negative, it fails."
>>        | firstLarge secondLarge firstLen secondLen shortLen shortLarge longLen longLarge result |
>>        (interpreterProxy isIntegerObject: firstInteger)
>>                ifTrue:
>> +                       [(interpreterProxy integerValueOf: firstInteger) < 0 ifTrue:
>> +                               [^ interpreterProxy primitiveFail].
>> -                       [(interpreterProxy integerValueOf: firstInteger)
>> -                               < 0 ifTrue: [^ interpreterProxy primitiveFail].
>>                        "convert it to a not normalized LargeInteger"
>>                        self remapOop: secondInteger in: [firstLarge := self createLargeFromSmallInteger: firstInteger]]
>>                ifFalse:
>>                        [(interpreterProxy isLargePositiveIntegerObject: firstInteger) ifFalse: [^ interpreterProxy primitiveFail].
>>                        firstLarge := firstInteger].
>>        (interpreterProxy isIntegerObject: secondInteger)
>>                ifTrue:
>> +                       [(interpreterProxy integerValueOf: secondInteger) < 0 ifTrue:
>> +                               [^ interpreterProxy primitiveFail].
>> -                       [(interpreterProxy integerValueOf: secondInteger)
>> -                               < 0 ifTrue: [^ interpreterProxy primitiveFail].
>>                        "convert it to a not normalized LargeInteger"
>>                        self remapOop: firstLarge in: [secondLarge := self createLargeFromSmallInteger: secondInteger]]
>>                ifFalse:
>>                        [(interpreterProxy isLargePositiveIntegerObject: secondInteger) ifFalse: [^ interpreterProxy primitiveFail].
>>                        secondLarge := secondInteger].
>>        firstLen := self byteSizeOfLargeInt: firstLarge.
>>        secondLen := self byteSizeOfLargeInt: secondLarge.
>>        firstLen < secondLen
>>                ifTrue:
>>                        [shortLen := firstLen.
>>                        shortLarge := firstLarge.
>>                        longLen := secondLen.
>>                        longLarge := secondLarge]
>>                ifFalse:
>>                        [shortLen := secondLen.
>>                        shortLarge := secondLarge.
>>                        longLen := firstLen.
>>                        longLarge := firstLarge].
>> +       self remapOop: #(shortLarge longLarge) in:
>> +               [result := interpreterProxy instantiateClass: interpreterProxy classLargePositiveInteger indexableSize: longLen].
>> +       result ifNil: [^interpreterProxy primitiveFailFor: PrimErrNoMemory].
>> -       self remapOop: #(shortLarge longLarge ) in: [result := interpreterProxy instantiateClass: interpreterProxy classLargePositiveInteger indexableSize: longLen].
>>        self
>>                cDigitOp: opIx
>>                short: (self pointerToFirstDigitOfLargeInt: shortLarge)
>>                len: shortLen + 3 // 4
>>                long: (self pointerToFirstDigitOfLargeInt: longLarge)
>>                len: longLen + 3 // 4
>>                into: (self pointerToFirstDigitOfLargeInt: result).
>>        interpreterProxy failed ifTrue: [^ 0].
>> +       ^self normalizePositive: result!
>> -       ^ self normalizePositive: result!
>> 
>> Item was changed:
>>  ----- Method: LargeIntegersPlugin>>digitMontgomery:times:modulo:mInvModB: (in category 'oop functions') -----
>>  digitMontgomery: firstLarge times: secondLarge modulo: thirdLarge mInvModB: mInv
>>        <var: #mInv type: #'unsigned int'>
>>        | firstLen secondLen thirdLen prod |
>>        firstLen := self digitSizeOfLargeInt: firstLarge.
>>        secondLen := self digitSizeOfLargeInt: secondLarge.
>>        thirdLen := self digitSizeOfLargeInt: thirdLarge.
>>        (firstLen <= thirdLen and: [secondLen <= thirdLen]) ifFalse: [^interpreterProxy primitiveFail].
>> 
>>        self remapOop: #(firstLarge secondLarge thirdLarge)
>>                in: [prod := interpreterProxy instantiateClass: interpreterProxy classLargePositiveInteger indexableSize: thirdLen * 4].
>> +       prod ifNil: [^interpreterProxy primitiveFailFor: PrimErrNoMemory].
>>        self
>>                cDigitMontgomery: (self pointerToFirstDigitOfLargeInt: firstLarge)
>>                len: firstLen
>>                times: (self pointerToFirstDigitOfLargeInt: secondLarge)
>>                len: secondLen
>>                modulo: (self pointerToFirstDigitOfLargeInt: thirdLarge)
>>                len: thirdLen
>>                mInvModB: mInv
>>                into: (self pointerToFirstDigitOfLargeInt: prod).
>>        ^self normalizePositive: prod!
>> 
>> Item was changed:
>>  ----- Method: LargeIntegersPlugin>>digitMultiplyLarge:with:negative: (in category 'oop functions') -----
>>  digitMultiplyLarge: firstInteger with: secondInteger negative: neg
>>        "Normalizes."
>>        | firstLen secondLen shortInt shortLen longInt longLen prod |
>>        firstLen := self byteSizeOfLargeInt: firstInteger.
>>        secondLen := self byteSizeOfLargeInt: secondInteger.
>>        firstLen <= secondLen
>>                ifTrue:
>>                        [shortInt := firstInteger.
>>                        shortLen := firstLen.
>>                        longInt := secondInteger.
>>                        longLen := secondLen]
>>                ifFalse:
>>                        [shortInt := secondInteger.
>>                        shortLen := secondLen.
>>                        longInt := firstInteger.
>>                        longLen := firstLen].
>>        self remapOop: #(shortInt longInt) in: [prod := self createLargeIntegerNeg: neg byteLength: longLen + shortLen].
>> +       prod ifNil: [^interpreterProxy primitiveFailFor: PrimErrNoMemory].
>>        self
>>                cDigitMultiply: (self pointerToFirstDigitOfLargeInt: shortInt)
>>                len: shortLen + 3 // 4
>>                with: (self pointerToFirstDigitOfLargeInt: longInt)
>>                len: longLen + 3 // 4
>>                into: (self pointerToFirstDigitOfLargeInt: prod)
>>                len: longLen + shortLen + 3 // 4.
>>        ^neg
>>                ifTrue: [self normalizeNegative: prod]
>>                ifFalse: [self normalizePositive: prod]!
>> 
>> Item was changed:
>>  ----- Method: LargeIntegersPlugin>>digitSubLarge:with: (in category 'oop functions') -----
>>  digitSubLarge: firstInteger with: secondInteger
>>        "Normalizes."
>>        | firstDigitLen secondDigitLen larger largeDigitLen smaller smallerDigitLen neg resDigitLen res firstNeg |
>>        firstNeg := interpreterProxy isLargeNegativeIntegerObject: firstInteger.
>>        firstDigitLen := self digitSizeOfLargeInt: firstInteger.
>>        secondDigitLen := self digitSizeOfLargeInt: secondInteger.
>>        firstDigitLen = secondDigitLen ifTrue:
>>                [[firstDigitLen > 1
>>                  and: [(self unsafeDigitOfLargeInt: firstInteger at: firstDigitLen) = (self unsafeDigitOfLargeInt: secondInteger at: firstDigitLen)]]
>>                        whileTrue: [firstDigitLen := firstDigitLen - 1].
>>                secondDigitLen := firstDigitLen].
>>        (firstDigitLen < secondDigitLen
>>         or: [firstDigitLen = secondDigitLen
>>                 and: [(self unsafeDigitOfLargeInt: firstInteger at: firstDigitLen) < (self unsafeDigitOfLargeInt: secondInteger at: firstDigitLen)]])
>>                ifTrue:
>>                        [larger := secondInteger.
>>                        largeDigitLen := secondDigitLen.
>>                        smaller := firstInteger.
>>                        smallerDigitLen := firstDigitLen.
>>                        neg := firstNeg == false]
>>                ifFalse:
>>                        [larger := firstInteger.
>>                        largeDigitLen := firstDigitLen.
>>                        smaller := secondInteger.
>>                        smallerDigitLen := secondDigitLen.
>>                        neg := firstNeg].
>>        resDigitLen := largeDigitLen.
>>        self remapOop: #(smaller larger)
>>                in: [res := self createLargeIntegerNeg: neg digitLength: resDigitLen].
>> +       res ifNil: [^interpreterProxy primitiveFailFor: PrimErrNoMemory].
>>        self
>>                cDigitSub: (self pointerToFirstDigitOfLargeInt: smaller)
>>                len: smallerDigitLen
>>                with: (self pointerToFirstDigitOfLargeInt: larger)
>>                len: largeDigitLen
>>                into: (self pointerToFirstDigitOfLargeInt: res).
>>        ^neg
>>                ifTrue: [self normalizeNegative: res]
>>                ifFalse: [self normalizePositive: res]!
>> 


More information about the Vm-dev mailing list