Reed Solomon plugins & performance slow down

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
29 messages Options
12
Reply | Threaded
Open this post in threaded view
|

Re: Reed Solomon plugins & performance slow down

Robert Withers-2
 

I am getting this warning when cross compiling the Squeak plugin to C code.

warning, signature of InterpreterProxy>>instantiateClass:indexableSize: does not match reference implementation.

---
Kindly,
Robert


On 6/4/21 1:21 PM, Robert Withers wrote:

Nope, this wasn't it.

---
Kindly,
Robert


On 6/4/21 12:36 PM, Robert wrote:
Oh! Heading for a coffee with my nurse. I realized I may be passing the field into the primitive instead of the field size. I’ll check it when I get back home!

Kindly,
Robert
. .. ... ‘...^,^


On Fri, Jun 4, 2021 at 12:12, Robert Withers <[hidden email]> wrote:
Oh! I forgot to relocate leaves that have already been plugganized. This leaves (heh) 3 possible plugganizations that all instantiate ByteArrays. Here, I fixed it.
WITH GF & GFPOLY PRIMITIVES AND DECODER PRIMITIVES
(3 asterix for in-progress plugganization)

 - 22194 tallies, 22648 msec.

**Leaves**
29.1% {6586ms} RSFECDecoderWithPlugin>>decode:twoS:
14.7% {3329ms} RSFECGenericGFPoly class>>newField:coefficients:
1.0% {237ms} RSFECDecoderWithPlugin>>runEuclideanAlgorithmPoly:poly:rDegrees:
Calls to plugganized GF/GFPoly methods, so I think these are as optimized as possible:
7.3% {1646ms} RSFECDecoderWithPlugin>>primFindErrorLocationsDegree:coefficients:result:fieldSize:
2.9% {654ms} RSFECDecoderWithPlugin>>findErrorMagnitudes:errorLocations:
1.4% {317ms} RSFECGenericGFWithPlugin>>log:
 
---
Kindly,
Robert


On 6/4/21 12:02 PM, Robert Withers wrote:
WITH GF & GFPOLY PRIMITIVES AND DECODER PRIMITIVES
(3 asterix for in-progress plugganization)

 - 22194 tallies, 22648 msec.

**Leaves**
29.1% {6586ms} RSFECDecoderWithPlugin>>decode:twoS:
14.7% {3329ms} RSFECGenericGFPoly class>>newField:coefficients:
7.3% {1646ms} RSFECDecoderWithPlugin>>primFindErrorLocationsDegree:coefficients:result:fieldSize:
2.9% {654ms} RSFECDecoderWithPlugin>>findErrorMagnitudes:errorLocations:
1.0% {237ms} RSFECDecoderWithPlugin>>runEuclideanAlgorithmPoly:poly:rDegrees:
Calls to plugganized GF/GFPoly methods:
1.4% {317ms} RSFECGenericGFWithPlugin>>log:


Reply | Threaded
Open this post in threaded view
|

Re: Reed Solomon plugins & performance slow down

Robert Withers-2
 

Hi Levente,

I hope you are having a great day! Are you in Budapest? That must be awesome! A very old city.

I thought I would post the Squeak code for this instantiatePoly primitive. My image still blows up on startUp:. I am grateful you have guided me through this!

primitiveInitializePolyFieldSizeCoefficients

    <export: true>
    <var: 'coefficients' type: 'unsigned char*' >

    | coefficients count coefficientsOop fieldSize result |
    interpreterProxy methodArgumentCount = 2
        ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadNumArgs ].
    fieldSize := interpreterProxy stackIntegerValue: 1.
    coefficientsOop := interpreterProxy stackObjectValue: 0.

    (interpreterProxy isIntegerValue: fieldSize)
        ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].
    (interpreterProxy isBytes: coefficientsOop)
        ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].
    count := interpreterProxy stSizeOf: coefficientsOop.
    coefficients := interpreterProxy firstIndexableField: coefficientsOop.

    (count = 0)
        ifTrue: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].

    result := self
        initializePolyFieldSize: fieldSize
        coefficients: coefficients
        coefficientsCount: count.

    ^ interpreterProxy failed
            ifTrue: [interpreterProxy primitiveFail]
            ifFalse: [interpreterProxy methodReturnValue: result].

Which is calling:

initializePolyFieldSize: fieldSize coefficients: coefficients coefficientsCount: coefficientsCount

    <var: 'coefficients' type: #'unsigned char*'>

    | coefficientsLength firstNonZero mutableCoefficients |
    mutableCoefficients := coefficients.
    coefficientsLength := coefficientsCount.
    ((coefficientsLength > 1) & ((coefficients at: 1) = 0))
        ifTrue: [
            firstNonZero := 2.
            [(firstNonZero <= coefficientsLength) and: [(mutableCoefficients at: firstNonZero) = 0]]
                whileTrue: [firstNonZero := firstNonZero + 1].
            (firstNonZero > coefficientsLength)
                ifTrue: [
                        mutableCoefficients := interpreterProxy
                            instantiateClass: interpreterProxy classByteArray
                            indexableSize: 1]
                ifFalse: [
                        mutableCoefficients := interpreterProxy
                            instantiateClass: interpreterProxy classByteArray
                            indexableSize: (coefficientsLength - firstNonZero + 1).
                        0 to: (coefficientsLength - 1)
                            do: [:index |
                                coefficients at: index put: (mutableCoefficients at: index)]]].
    ^ mutableCoefficients.


---
Köszönöm,
Robert


On 6/4/21 1:38 PM, Robert Withers wrote:

I am getting this warning when cross compiling the Squeak plugin to C code.

warning, signature of InterpreterProxy>>instantiateClass:indexableSize: does not match reference implementation.

---
Kindly,
Robert


On 6/4/21 1:21 PM, Robert Withers wrote:

Nope, this wasn't it.

---
Kindly,
Robert


On 6/4/21 12:36 PM, Robert wrote:
Oh! Heading for a coffee with my nurse. I realized I may be passing the field into the primitive instead of the field size. I’ll check it when I get back home!

Kindly,
Robert
. .. ... ‘...^,^


On Fri, Jun 4, 2021 at 12:12, Robert Withers <[hidden email]> wrote:
Oh! I forgot to relocate leaves that have already been plugganized. This leaves (heh) 3 possible plugganizations that all instantiate ByteArrays. Here, I fixed it.
WITH GF & GFPOLY PRIMITIVES AND DECODER PRIMITIVES
(3 asterix for in-progress plugganization)

 - 22194 tallies, 22648 msec.

**Leaves**
29.1% {6586ms} RSFECDecoderWithPlugin>>decode:twoS:
14.7% {3329ms} RSFECGenericGFPoly class>>newField:coefficients:
1.0% {237ms} RSFECDecoderWithPlugin>>runEuclideanAlgorithmPoly:poly:rDegrees:
Calls to plugganized GF/GFPoly methods, so I think these are as optimized as possible:
7.3% {1646ms} RSFECDecoderWithPlugin>>primFindErrorLocationsDegree:coefficients:result:fieldSize:
2.9% {654ms} RSFECDecoderWithPlugin>>findErrorMagnitudes:errorLocations:
1.4% {317ms} RSFECGenericGFWithPlugin>>log:
 
---
Kindly,
Robert


On 6/4/21 12:02 PM, Robert Withers wrote:
WITH GF & GFPOLY PRIMITIVES AND DECODER PRIMITIVES
(3 asterix for in-progress plugganization)

 - 22194 tallies, 22648 msec.

**Leaves**
29.1% {6586ms} RSFECDecoderWithPlugin>>decode:twoS:
14.7% {3329ms} RSFECGenericGFPoly class>>newField:coefficients:
7.3% {1646ms} RSFECDecoderWithPlugin>>primFindErrorLocationsDegree:coefficients:result:fieldSize:
2.9% {654ms} RSFECDecoderWithPlugin>>findErrorMagnitudes:errorLocations:
1.0% {237ms} RSFECDecoderWithPlugin>>runEuclideanAlgorithmPoly:poly:rDegrees:
Calls to plugganized GF/GFPoly methods:
1.4% {317ms} RSFECGenericGFWithPlugin>>log:


Reply | Threaded
Open this post in threaded view
|

Re: Reed Solomon plugins & performance slow down

Robert Withers-2
 

I consolidated the RS Plugins into 1 RSPlugin class. Here is the new load script:

Installer ss
    project: 'Cryptography';
    install: 'ProCrypto-1-1-1';
    install: 'ProCryptoTests-1-1-1';
    install: 'CryptographyRSPlugin'.


---
Kindly,
Robert


On 6/4/21 2:51 PM, Robert Withers wrote:

Hi Levente,

I hope you are having a great day! Are you in Budapest? That must be awesome! A very old city.

I thought I would post the Squeak code for this instantiatePoly primitive. My image still blows up on startUp:. I am grateful you have guided me through this!

primitiveInitializePolyFieldSizeCoefficients

    <export: true>
    <var: 'coefficients' type: 'unsigned char*' >

    | coefficients count coefficientsOop fieldSize result |
    interpreterProxy methodArgumentCount = 2
        ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadNumArgs ].
    fieldSize := interpreterProxy stackIntegerValue: 1.
    coefficientsOop := interpreterProxy stackObjectValue: 0.

    (interpreterProxy isIntegerValue: fieldSize)
        ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].
    (interpreterProxy isBytes: coefficientsOop)
        ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].
    count := interpreterProxy stSizeOf: coefficientsOop.
    coefficients := interpreterProxy firstIndexableField: coefficientsOop.

    (count = 0)
        ifTrue: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].

    result := self
        initializePolyFieldSize: fieldSize
        coefficients: coefficients
        coefficientsCount: count.

    ^ interpreterProxy failed
            ifTrue: [interpreterProxy primitiveFail]
            ifFalse: [interpreterProxy methodReturnValue: result].

Which is calling:

initializePolyFieldSize: fieldSize coefficients: coefficients coefficientsCount: coefficientsCount

    <var: 'coefficients' type: #'unsigned char*'>

    | coefficientsLength firstNonZero mutableCoefficients |
    mutableCoefficients := coefficients.
    coefficientsLength := coefficientsCount.
    ((coefficientsLength > 1) & ((coefficients at: 1) = 0))
        ifTrue: [
            firstNonZero := 2.
            [(firstNonZero <= coefficientsLength) and: [(mutableCoefficients at: firstNonZero) = 0]]
                whileTrue: [firstNonZero := firstNonZero + 1].
            (firstNonZero > coefficientsLength)
                ifTrue: [
                        mutableCoefficients := interpreterProxy
                            instantiateClass: interpreterProxy classByteArray
                            indexableSize: 1]
                ifFalse: [
                        mutableCoefficients := interpreterProxy
                            instantiateClass: interpreterProxy classByteArray
                            indexableSize: (coefficientsLength - firstNonZero + 1).
                        0 to: (coefficientsLength - 1)
                            do: [:index |
                                coefficients at: index put: (mutableCoefficients at: index)]]].
    ^ mutableCoefficients.


---
Köszönöm,
Robert


On 6/4/21 1:38 PM, Robert Withers wrote:

I am getting this warning when cross compiling the Squeak plugin to C code.

warning, signature of InterpreterProxy>>instantiateClass:indexableSize: does not match reference implementation.

---
Kindly,
Robert


On 6/4/21 1:21 PM, Robert Withers wrote:

Nope, this wasn't it.

---
Kindly,
Robert


On 6/4/21 12:36 PM, Robert wrote:
Oh! Heading for a coffee with my nurse. I realized I may be passing the field into the primitive instead of the field size. I’ll check it when I get back home!

Kindly,
Robert
. .. ... ‘...^,^


On Fri, Jun 4, 2021 at 12:12, Robert Withers <[hidden email]> wrote:
Oh! I forgot to relocate leaves that have already been plugganized. This leaves (heh) 3 possible plugganizations that all instantiate ByteArrays. Here, I fixed it.
WITH GF & GFPOLY PRIMITIVES AND DECODER PRIMITIVES
(3 asterix for in-progress plugganization)

 - 22194 tallies, 22648 msec.

**Leaves**
29.1% {6586ms} RSFECDecoderWithPlugin>>decode:twoS:
14.7% {3329ms} RSFECGenericGFPoly class>>newField:coefficients:
1.0% {237ms} RSFECDecoderWithPlugin>>runEuclideanAlgorithmPoly:poly:rDegrees:
Calls to plugganized GF/GFPoly methods, so I think these are as optimized as possible:
7.3% {1646ms} RSFECDecoderWithPlugin>>primFindErrorLocationsDegree:coefficients:result:fieldSize:
2.9% {654ms} RSFECDecoderWithPlugin>>findErrorMagnitudes:errorLocations:
1.4% {317ms} RSFECGenericGFWithPlugin>>log:
 
---
Kindly,
Robert


On 6/4/21 12:02 PM, Robert Withers wrote:
WITH GF & GFPOLY PRIMITIVES AND DECODER PRIMITIVES
(3 asterix for in-progress plugganization)

 - 22194 tallies, 22648 msec.

**Leaves**
29.1% {6586ms} RSFECDecoderWithPlugin>>decode:twoS:
14.7% {3329ms} RSFECGenericGFPoly class>>newField:coefficients:
7.3% {1646ms} RSFECDecoderWithPlugin>>primFindErrorLocationsDegree:coefficients:result:fieldSize:
2.9% {654ms} RSFECDecoderWithPlugin>>findErrorMagnitudes:errorLocations:
1.0% {237ms} RSFECDecoderWithPlugin>>runEuclideanAlgorithmPoly:poly:rDegrees:
Calls to plugganized GF/GFPoly methods:
1.4% {317ms} RSFECGenericGFWithPlugin>>log:


Reply | Threaded
Open this post in threaded view
|

Re: Reed Solomon plugins & performance slow down

Robert Withers-2
 

A bit more detail on my refactoring. I combined the Plugins to 1 RSPlugin.

I updated the package: CryptographyRSPluginExtending to include all problematic primitives and their send sites. This includes GFPolyWithPlugin>>#initializeField:coefficients: and the ErasureOutputByteInputCodingLoopWithPlugin methods. To load this extension (which blows up the image by the way) run this compound script:

Installer ss
    project: 'Cryptography';
    install: 'ProCrypto-1-1-1';
    install: 'ProCryptoTests-1-1-1';
    install: 'CryptographyRSPlugin'.

Installer ss
    project: 'Cryptography';
    install: 'CryptographyRSPluginExtending'.

To unload and restore prior functionality, run this compound script:

Installer ss
    project: 'Cryptography';
    unload: 'CryptographyRSPluginExtending'.

Installer ss
    project: 'Cryptography';
    install: 'CryptographyRSErasure';
    install: 'CryptographyRSFEC';
    install: 'CryptographyRSPlugin'.

That is all.
---
Kindly,
Robert


On 6/5/21 8:34 AM, Robert Withers wrote:

I consolidated the RS Plugins into 1 RSPlugin class. Here is the new load script:

Installer ss
    project: 'Cryptography';
    install: 'ProCrypto-1-1-1';
    install: 'ProCryptoTests-1-1-1';
    install: 'CryptographyRSPlugin'.


---
Kindly,
Robert


On 6/4/21 2:51 PM, Robert Withers wrote:

Hi Levente,

I hope you are having a great day! Are you in Budapest? That must be awesome! A very old city.

I thought I would post the Squeak code for this instantiatePoly primitive. My image still blows up on startUp:. I am grateful you have guided me through this!

primitiveInitializePolyFieldSizeCoefficients

    <export: true>
    <var: 'coefficients' type: 'unsigned char*' >

    | coefficients count coefficientsOop fieldSize result |
    interpreterProxy methodArgumentCount = 2
        ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadNumArgs ].
    fieldSize := interpreterProxy stackIntegerValue: 1.
    coefficientsOop := interpreterProxy stackObjectValue: 0.

    (interpreterProxy isIntegerValue: fieldSize)
        ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].
    (interpreterProxy isBytes: coefficientsOop)
        ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].
    count := interpreterProxy stSizeOf: coefficientsOop.
    coefficients := interpreterProxy firstIndexableField: coefficientsOop.

    (count = 0)
        ifTrue: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].

    result := self
        initializePolyFieldSize: fieldSize
        coefficients: coefficients
        coefficientsCount: count.

    ^ interpreterProxy failed
            ifTrue: [interpreterProxy primitiveFail]
            ifFalse: [interpreterProxy methodReturnValue: result].

Which is calling:

initializePolyFieldSize: fieldSize coefficients: coefficients coefficientsCount: coefficientsCount

    <var: 'coefficients' type: #'unsigned char*'>

    | coefficientsLength firstNonZero mutableCoefficients |
    mutableCoefficients := coefficients.
    coefficientsLength := coefficientsCount.
    ((coefficientsLength > 1) & ((coefficients at: 1) = 0))
        ifTrue: [
            firstNonZero := 2.
            [(firstNonZero <= coefficientsLength) and: [(mutableCoefficients at: firstNonZero) = 0]]
                whileTrue: [firstNonZero := firstNonZero + 1].
            (firstNonZero > coefficientsLength)
                ifTrue: [
                        mutableCoefficients := interpreterProxy
                            instantiateClass: interpreterProxy classByteArray
                            indexableSize: 1]
                ifFalse: [
                        mutableCoefficients := interpreterProxy
                            instantiateClass: interpreterProxy classByteArray
                            indexableSize: (coefficientsLength - firstNonZero + 1).
                        0 to: (coefficientsLength - 1)
                            do: [:index |
                                coefficients at: index put: (mutableCoefficients at: index)]]].
    ^ mutableCoefficients.


---
Köszönöm,
Robert


On 6/4/21 1:38 PM, Robert Withers wrote:

I am getting this warning when cross compiling the Squeak plugin to C code.

warning, signature of InterpreterProxy>>instantiateClass:indexableSize: does not match reference implementation.

---
Kindly,
Robert


On 6/4/21 1:21 PM, Robert Withers wrote:

Nope, this wasn't it.

---
Kindly,
Robert


On 6/4/21 12:36 PM, Robert wrote:
Oh! Heading for a coffee with my nurse. I realized I may be passing the field into the primitive instead of the field size. I’ll check it when I get back home!

Kindly,
Robert
. .. ... ‘...^,^


On Fri, Jun 4, 2021 at 12:12, Robert Withers <[hidden email]> wrote:
Oh! I forgot to relocate leaves that have already been plugganized. This leaves (heh) 3 possible plugganizations that all instantiate ByteArrays. Here, I fixed it.
WITH GF & GFPOLY PRIMITIVES AND DECODER PRIMITIVES
(3 asterix for in-progress plugganization)

 - 22194 tallies, 22648 msec.

**Leaves**
29.1% {6586ms} RSFECDecoderWithPlugin>>decode:twoS:
14.7% {3329ms} RSFECGenericGFPoly class>>newField:coefficients:
1.0% {237ms} RSFECDecoderWithPlugin>>runEuclideanAlgorithmPoly:poly:rDegrees:
Calls to plugganized GF/GFPoly methods, so I think these are as optimized as possible:
7.3% {1646ms} RSFECDecoderWithPlugin>>primFindErrorLocationsDegree:coefficients:result:fieldSize:
2.9% {654ms} RSFECDecoderWithPlugin>>findErrorMagnitudes:errorLocations:
1.4% {317ms} RSFECGenericGFWithPlugin>>log:
 
---
Kindly,
Robert


On 6/4/21 12:02 PM, Robert Withers wrote:
WITH GF & GFPOLY PRIMITIVES AND DECODER PRIMITIVES
(3 asterix for in-progress plugganization)

 - 22194 tallies, 22648 msec.

**Leaves**
29.1% {6586ms} RSFECDecoderWithPlugin>>decode:twoS:
14.7% {3329ms} RSFECGenericGFPoly class>>newField:coefficients:
7.3% {1646ms} RSFECDecoderWithPlugin>>primFindErrorLocationsDegree:coefficients:result:fieldSize:
2.9% {654ms} RSFECDecoderWithPlugin>>findErrorMagnitudes:errorLocations:
1.0% {237ms} RSFECDecoderWithPlugin>>runEuclideanAlgorithmPoly:poly:rDegrees:
Calls to plugganized GF/GFPoly methods:
1.4% {317ms} RSFECGenericGFWithPlugin>>log:


Reply | Threaded
Open this post in threaded view
|

Re: Reed Solomon plugins & performance slow down

Robert Withers-2
 

CryptographyRSPluginExtending-rww.7.mcz now has all 7 missing primitives, for the FECDecoder, the GFPoly and the GaloisCodingLoop. Here is a list.

  1. GaloisCodingLoopOutputByteInputExpCodingLoopWithPlugin>>#primCheckSomeShardsMatrixRows: matrixRows
        inputs: inputs
        toCheck: toCheck
        offset: offset
        byteCount: byteCount
  2. GaloisCodingLoopOutputByteInputExpCodingLoopWithPlugin>>#primCodeSomeShardsMatrixRows: matrixRows
        inputs: inputs
        outputs: outputs
        offset: offset
        byteCount: byteCount
  3. GaloisCodingLoopOutputByteInputExpCodingLoopWithPlugin>>#primComputeValueMatrixRow: matrixRow
        inputs: inputs
        inputIndex: inputIndex
        byteIndex: byteIndex
        value: value
  4. FECGFPolyWithPlugin>>#primInitializePolyFieldSize:  fieldSize
        coefficients: localCoefficients
  5. FECGFPolyWithPlugin>>#primDividePolySelfCoefficients: coefficients
        otherCoefficients: otherCoefficients
        fieldSize: fieldSize
  6. FECDecoderWithPlugin>>#primDecode: decoded
        twoS: twoS
        generatorBase: generatorBase
  7. FECDecoderWithPlugin>>#primRunEuclideanAlgorithmPolyA: polyA
        polyB: polyB
        degrees: fieldSize
---
Kindly,
Robert


On 6/5/21 9:50 AM, Robert Withers wrote:

A bit more detail on my refactoring. I combined the Plugins to 1 RSPlugin.

I updated the package: CryptographyRSPluginExtending to include all problematic primitives and their send sites. This includes GFPolyWithPlugin>>#initializeField:coefficients: and the ErasureOutputByteInputCodingLoopWithPlugin methods. To load this extension (which blows up the image by the way) run this compound script:

Installer ss
    project: 'Cryptography';
    install: 'ProCrypto-1-1-1';
    install: 'ProCryptoTests-1-1-1';
    install: 'CryptographyRSPlugin'.

Installer ss
    project: 'Cryptography';
    install: 'CryptographyRSPluginExtending'.

To unload and restore prior functionality, run this compound script:

Installer ss
    project: 'Cryptography';
    unload: 'CryptographyRSPluginExtending'.

Installer ss
    project: 'Cryptography';
    install: 'CryptographyRSErasure';
    install: 'CryptographyRSFEC';
    install: 'CryptographyRSPlugin'.

That is all.
---
Kindly,
Robert


On 6/5/21 8:34 AM, Robert Withers wrote:

I consolidated the RS Plugins into 1 RSPlugin class. Here is the new load script:

Installer ss
    project: 'Cryptography';
    install: 'ProCrypto-1-1-1';
    install: 'ProCryptoTests-1-1-1';
    install: 'CryptographyRSPlugin'.


---
Kindly,
Robert


On 6/4/21 2:51 PM, Robert Withers wrote:

Hi Levente,

I hope you are having a great day! Are you in Budapest? That must be awesome! A very old city.

I thought I would post the Squeak code for this instantiatePoly primitive. My image still blows up on startUp:. I am grateful you have guided me through this!

primitiveInitializePolyFieldSizeCoefficients

    <export: true>
    <var: 'coefficients' type: 'unsigned char*' >

    | coefficients count coefficientsOop fieldSize result |
    interpreterProxy methodArgumentCount = 2
        ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadNumArgs ].
    fieldSize := interpreterProxy stackIntegerValue: 1.
    coefficientsOop := interpreterProxy stackObjectValue: 0.

    (interpreterProxy isIntegerValue: fieldSize)
        ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].
    (interpreterProxy isBytes: coefficientsOop)
        ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].
    count := interpreterProxy stSizeOf: coefficientsOop.
    coefficients := interpreterProxy firstIndexableField: coefficientsOop.

    (count = 0)
        ifTrue: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].

    result := self
        initializePolyFieldSize: fieldSize
        coefficients: coefficients
        coefficientsCount: count.

    ^ interpreterProxy failed
            ifTrue: [interpreterProxy primitiveFail]
            ifFalse: [interpreterProxy methodReturnValue: result].

Which is calling:

initializePolyFieldSize: fieldSize coefficients: coefficients coefficientsCount: coefficientsCount

    <var: 'coefficients' type: #'unsigned char*'>

    | coefficientsLength firstNonZero mutableCoefficients |
    mutableCoefficients := coefficients.
    coefficientsLength := coefficientsCount.
    ((coefficientsLength > 1) & ((coefficients at: 1) = 0))
        ifTrue: [
            firstNonZero := 2.
            [(firstNonZero <= coefficientsLength) and: [(mutableCoefficients at: firstNonZero) = 0]]
                whileTrue: [firstNonZero := firstNonZero + 1].
            (firstNonZero > coefficientsLength)
                ifTrue: [
                        mutableCoefficients := interpreterProxy
                            instantiateClass: interpreterProxy classByteArray
                            indexableSize: 1]
                ifFalse: [
                        mutableCoefficients := interpreterProxy
                            instantiateClass: interpreterProxy classByteArray
                            indexableSize: (coefficientsLength - firstNonZero + 1).
                        0 to: (coefficientsLength - 1)
                            do: [:index |
                                coefficients at: index put: (mutableCoefficients at: index)]]].
    ^ mutableCoefficients.


---
Köszönöm,
Robert


On 6/4/21 1:38 PM, Robert Withers wrote:

I am getting this warning when cross compiling the Squeak plugin to C code.

warning, signature of InterpreterProxy>>instantiateClass:indexableSize: does not match reference implementation.

---
Kindly,
Robert


On 6/4/21 1:21 PM, Robert Withers wrote:

Nope, this wasn't it.

---
Kindly,
Robert


On 6/4/21 12:36 PM, Robert wrote:
Oh! Heading for a coffee with my nurse. I realized I may be passing the field into the primitive instead of the field size. I’ll check it when I get back home!

Kindly,
Robert
. .. ... ‘...^,^


On Fri, Jun 4, 2021 at 12:12, Robert Withers <[hidden email]> wrote:
Oh! I forgot to relocate leaves that have already been plugganized. This leaves (heh) 3 possible plugganizations that all instantiate ByteArrays. Here, I fixed it.
WITH GF & GFPOLY PRIMITIVES AND DECODER PRIMITIVES
(3 asterix for in-progress plugganization)

 - 22194 tallies, 22648 msec.

**Leaves**
29.1% {6586ms} RSFECDecoderWithPlugin>>decode:twoS:
14.7% {3329ms} RSFECGenericGFPoly class>>newField:coefficients:
1.0% {237ms} RSFECDecoderWithPlugin>>runEuclideanAlgorithmPoly:poly:rDegrees:
Calls to plugganized GF/GFPoly methods, so I think these are as optimized as possible:
7.3% {1646ms} RSFECDecoderWithPlugin>>primFindErrorLocationsDegree:coefficients:result:fieldSize:
2.9% {654ms} RSFECDecoderWithPlugin>>findErrorMagnitudes:errorLocations:
1.4% {317ms} RSFECGenericGFWithPlugin>>log:
 
---
Kindly,
Robert


On 6/4/21 12:02 PM, Robert Withers wrote:
WITH GF & GFPOLY PRIMITIVES AND DECODER PRIMITIVES
(3 asterix for in-progress plugganization)

 - 22194 tallies, 22648 msec.

**Leaves**
29.1% {6586ms} RSFECDecoderWithPlugin>>decode:twoS:
14.7% {3329ms} RSFECGenericGFPoly class>>newField:coefficients:
7.3% {1646ms} RSFECDecoderWithPlugin>>primFindErrorLocationsDegree:coefficients:result:fieldSize:
2.9% {654ms} RSFECDecoderWithPlugin>>findErrorMagnitudes:errorLocations:
1.0% {237ms} RSFECDecoderWithPlugin>>runEuclideanAlgorithmPoly:poly:rDegrees:
Calls to plugganized GF/GFPoly methods:
1.4% {317ms} RSFECGenericGFWithPlugin>>log:


Reply | Threaded
Open this post in threaded view
|

Re: Reed Solomon plugins & performance slow down

Eliot Miranda-2
In reply to this post by Robert Withers-2
 
Hi Robert,

On Jun 4, 2021, at 10:38 AM, Robert Withers <[hidden email]> wrote:



I am getting this warning when cross compiling the Squeak plugin to C code.

warning, signature of InterpreterProxy>>instantiateClass:indexableSize: does not match reference implementation.


Alas this is difficult to fix.  But it is safe to ignore this warningz

---
Kindly,
Robert


On 6/4/21 1:21 PM, Robert Withers wrote:

Nope, this wasn't it.

---
Kindly,
Robert


On 6/4/21 12:36 PM, Robert wrote:
Oh! Heading for a coffee with my nurse. I realized I may be passing the field into the primitive instead of the field size. I’ll check it when I get back home!

Kindly,
Robert
. .. ... ‘...^,^


On Fri, Jun 4, 2021 at 12:12, Robert Withers <[hidden email]> wrote:
Oh! I forgot to relocate leaves that have already been plugganized. This leaves (heh) 3 possible plugganizations that all instantiate ByteArrays. Here, I fixed it.
WITH GF & GFPOLY PRIMITIVES AND DECODER PRIMITIVES
(3 asterix for in-progress plugganization)

 - 22194 tallies, 22648 msec.

**Leaves**
29.1% {6586ms} RSFECDecoderWithPlugin>>decode:twoS:
14.7% {3329ms} RSFECGenericGFPoly class>>newField:coefficients:
1.0% {237ms} RSFECDecoderWithPlugin>>runEuclideanAlgorithmPoly:poly:rDegrees:
Calls to plugganized GF/GFPoly methods, so I think these are as optimized as possible:
7.3% {1646ms} RSFECDecoderWithPlugin>>primFindErrorLocationsDegree:coefficients:result:fieldSize:
2.9% {654ms} RSFECDecoderWithPlugin>>findErrorMagnitudes:errorLocations:
1.4% {317ms} RSFECGenericGFWithPlugin>>log:
 
---
Kindly,
Robert


On 6/4/21 12:02 PM, Robert Withers wrote:
WITH GF & GFPOLY PRIMITIVES AND DECODER PRIMITIVES
(3 asterix for in-progress plugganization)

 - 22194 tallies, 22648 msec.

**Leaves**
29.1% {6586ms} RSFECDecoderWithPlugin>>decode:twoS:
14.7% {3329ms} RSFECGenericGFPoly class>>newField:coefficients:
7.3% {1646ms} RSFECDecoderWithPlugin>>primFindErrorLocationsDegree:coefficients:result:fieldSize:
2.9% {654ms} RSFECDecoderWithPlugin>>findErrorMagnitudes:errorLocations:
1.0% {237ms} RSFECDecoderWithPlugin>>runEuclideanAlgorithmPoly:poly:rDegrees:
Calls to plugganized GF/GFPoly methods:
1.4% {317ms} RSFECGenericGFWithPlugin>>log:

Eliot
_,,,^..^,,,_ (phone)
Reply | Threaded
Open this post in threaded view
|

Re: Reed Solomon plugins & performance slow down

Eliot Miranda-2
In reply to this post by Robert Withers-2
 
Hi Robert,

_,,,^..^,,,_ (phone)

> On Jun 4, 2021, at 11:52 AM, Robert Withers <[hidden email]> wrote:
>
> fieldSize := interpreterProxy stackIntegerValue: 1.
>     coefficientsOop := interpreterProxy stackObjectValue: 0.

Since you check for isBytes: below you can use stackValue:. isBytes: can safely be passed any object, including immediates.  So the stackObjectValue: call implies a redundant validation.

>
>     (interpreterProxy isIntegerValue: fieldSize)
>         ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].

This is implicit. stackIntegerValue: fails if the object is not a SmallInteger (retiring zero) and otherwise answers its integerValue. So you should check if stackIntegerValue: fails since its return value will always answer true to isIntegerValue:

>     (interpreterProxy isBytes: coefficientsOop)
>         ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].

I would write

fieldSize := interpreterProxy stackIntegerValue: 1.
    coefficientsOop := interpreterProxy stackValue: 0.

    (interpreterProxy failed not
     and: [interpreterProxy isBytes: coefficientsOop])
        ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].

or

fieldSizeOop := interpreterProxy stackValue: 1.
    coefficientsOop := interpreterProxy stackValue: 0.

    ((interpreterProxy isIntegerObject: fieldSizeOop)
     and: [interpreterProxy isBytes: coefficientsOop])
        ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].

    fieldSize := interpreterProxy integerValueOf: fieldSizeOop.

Reply | Threaded
Open this post in threaded view
|

Re: Reed Solomon plugins & performance slow down

Robert Withers-2
 
Hi Eliot, I hope all is well with you! 

I will try to make these changes, both in my working primitives and in my 7 broken primitives. See if that might help.

Grazie Mille!

Kindly,
Robert
. .. ... ‘...^,^


On Sat, Jun 5, 2021 at 19:39, Eliot Miranda <[hidden email]> wrote:
Hi Robert,

_,,,^..^,,,_ (phone)

> On Jun 4, 2021, at 11:52 AM, Robert Withers <[hidden email]> wrote:
>
> fieldSize := interpreterProxy stackIntegerValue: 1.
> coefficientsOop := interpreterProxy stackObjectValue: 0.

Since you check for isBytes: below you can use stackValue:. isBytes: can safely be passed any object, including immediates. So the stackObjectValue: call implies a redundant validation.

>
> (interpreterProxy isIntegerValue: fieldSize)
> ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].

This is implicit. stackIntegerValue: fails if the object is not a SmallInteger (retiring zero) and otherwise answers its integerValue. So you should check if stackIntegerValue: fails since its return value will always answer true to isIntegerValue:

> (interpreterProxy isBytes: coefficientsOop)
> ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].

I would write

fieldSize := interpreterProxy stackIntegerValue: 1.
coefficientsOop := interpreterProxy stackValue: 0.

(interpreterProxy failed not
and: [interpreterProxy isBytes: coefficientsOop])
ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].

or

fieldSizeOop := interpreterProxy stackValue: 1.
coefficientsOop := interpreterProxy stackValue: 0.

((interpreterProxy isIntegerObject: fieldSizeOop)
and: [interpreterProxy isBytes: coefficientsOop])
ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].

fieldSize := interpreterProxy integerValueOf: fieldSizeOop.



Reply | Threaded
Open this post in threaded view
|

Re: Reed Solomon plugins & performance slow down

Robert Withers-2
In reply to this post by Eliot Miranda-2
 

Alright, Eliot! I finally got the changes made. You know that time when you have 2 images and you do the work in one and forget, then delete that one and have to recode all those changes? Exactly.

Nonetheless, I got the changes made and did a test of creating a ByteArray in a primitive/computation method:

#fecAddOrSubtractPolySelfCoefficients:selfCount:otherCoefficients:otherCount:.

In my case, I decided to create the result ByteArray in the computation method and return the resultOop to the primitive for #methodReturnValue:. Here is the primitive, followed by the computation method. This seems to work as I compiled and tested it. One consideration is that if we are in a primitive and call another, like happens in the decode methods, then I must remember to #interpreterProxy firstIndexableField: resultOop to access the array again (pass as argument to yet another compute method, for instance). Is this the best approach?

    resultOop := self
        fecAddOrSubtractPolySelfCoefficients: selfCoefficients
        selfCount: selfCount
        otherCoefficients: otherCoefficients
        otherCount: otherCount.

    ^ interpreterProxy failed
            ifTrue: [interpreterProxy primitiveFail]
            ifFalse: [interpreterProxy methodReturnValue: resultOop].

And the computation method

    resultOop := interpreterProxy
                instantiateClass: interpreterProxy classByteArray
                indexableSize: (selfCount max: otherCount).
    result := interpreterProxy firstIndexableField: resultOop.


    ^ resultOop


---
Kindly,
Robert


On 6/5/21 7:39 PM, Eliot Miranda wrote:
Hi Robert,

_,,,^..^,,,_ (phone)

On Jun 4, 2021, at 11:52 AM, Robert Withers [hidden email] wrote:

fieldSize := interpreterProxy stackIntegerValue: 1.
    coefficientsOop := interpreterProxy stackObjectValue: 0.
Since you check for isBytes: below you can use stackValue:. isBytes: can safely be passed any object, including immediates.  So the stackObjectValue: call implies a redundant validation.

    (interpreterProxy isIntegerValue: fieldSize)
        ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].
This is implicit. stackIntegerValue: fails if the object is not a SmallInteger (retiring zero) and otherwise answers its integerValue. So you should check if stackIntegerValue: fails since its return value will always answer true to isIntegerValue:

    (interpreterProxy isBytes: coefficientsOop)
        ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].
I would write

fieldSize := interpreterProxy stackIntegerValue: 1.
    coefficientsOop := interpreterProxy stackValue: 0.

    (interpreterProxy failed not
     and: [interpreterProxy isBytes: coefficientsOop])
        ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].

or

fieldSizeOop := interpreterProxy stackValue: 1.
    coefficientsOop := interpreterProxy stackValue: 0.

    ((interpreterProxy isIntegerObject: fieldSizeOop)
     and: [interpreterProxy isBytes: coefficientsOop])
        ifFalse: [ ^interpreterProxy primitiveFailFor: PrimErrBadArgument ].

    fieldSize := interpreterProxy integerValueOf: fieldSizeOop.

12