VM Maker: VMMaker.oscog-eem.2338.mcz

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

VM Maker: VMMaker.oscog-eem.2338.mcz

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

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

Name: VMMaker.oscog-eem.2338
Author: eem
Time: 22 February 2018, 10:25:17.794166 am
UUID: 1672c678-41b4-41f2-a061-e201562fc75c
Ancestors: VMMaker.oscog-eem.2337

Fix a slip in primitiveDecompressFromByteArray caught by IncludedMethodsTests.  Thank you David!

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

Item was changed:
  ----- Method: MiscPrimitivePlugin>>primitiveDecompressFromByteArray (in category 'primitives') -----
  primitiveDecompressFromByteArray
  "Bitmap decompress: bm fromByteArray: ba at: index"
  <export: true>
  | bm ba index i anInt code data end k n pastEnd |
  <var: 'ba' type: #'unsigned char *'>
  <var: 'bm' type: #'int *'>
  <var: 'anInt' type: #'unsigned int'>
  <var: 'code' type: #'unsigned int'>
  <var: 'data' type: #'unsigned int'>
  <var: 'n' type: #'unsigned int'>
  bm := self cCode: [interpreterProxy arrayValueOf: (interpreterProxy stackValue: 2)]
  inSmalltalk: [interpreterProxy
  cCoerce: (interpreterProxy arrayValueOf: (interpreterProxy stackValue: 2))
  to: #'int *'].
  (interpreterProxy isOopImmutable: (interpreterProxy stackValue: 2)) ifTrue:
  [^interpreterProxy primitiveFailFor: PrimErrNoModification].
  (interpreterProxy isBytes: (interpreterProxy stackValue: 1)) ifFalse: [^interpreterProxy primitiveFail].
  ba := interpreterProxy firstIndexableField: (interpreterProxy stackValue: 1).
  index := interpreterProxy stackIntegerValue: 0.
  interpreterProxy failed ifTrue: [^nil].
  i := index - 1.
  k := 0.
  end := interpreterProxy sizeOfSTArrayFromCPrimitive: ba.
  pastEnd := interpreterProxy sizeOfSTArrayFromCPrimitive: bm.
  [i < end] whileTrue:
  [anInt := ba at: i.
  i := i + 1.
  anInt <= 223 ifFalse:
  [anInt <= 254
  ifTrue:
  [anInt := anInt - 224 * 256 + (ba at: i).
  i := i + 1]
  ifFalse:
  [anInt := 0.
  1 to: 4 by: 1 do:
  [ :j | anInt := (anInt bitShift: 8) + (ba at: i).
  i := i + 1]]].
  n := anInt >> 2.
+ k + n > pastEnd ifTrue: [^interpreterProxy primitiveFail].
- k + n >= pastEnd ifTrue: [^interpreterProxy primitiveFail].
  code := anInt bitAnd: 3.
  "code = 0 ifTrue: [nil]."
  code = 1 ifTrue:
  [data := ba at: i.
  i := i + 1.
  data := data bitOr: (data bitShift: 8).
  data := data bitOr: (data bitShift: 16).
  1 to: n do:
  [ :j |
  bm at: k put: data.
  k := k + 1]].
  code = 2 ifTrue:
  [data := 0.
  1 to: 4 do:
  [ :j |
  data := (data bitShift: 8) bitOr: (ba at: i).
  i := i + 1].
  1 to: n do:
  [ :j |
  bm at: k put: data.
  k := k + 1]].
  code = 3 ifTrue:
  [1 to: n do:
  [ :m |
  data := 0.
  1 to: 4 do:
  [ :j |
  data := (data bitShift: 8) bitOr: (ba at: i).
  i := i + 1].
  bm at: k put: data.
  k := k + 1]]].
  interpreterProxy pop: interpreterProxy methodArgumentCount!

Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-eem.2338.mcz

Levente Uzonyi
 
Just had a look at this snippet, and wrote some quick inline comments.

On Thu, 22 Feb 2018, [hidden email] wrote:

>
> Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
> http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2338.mcz
>
> ==================== Summary ====================
>
> Name: VMMaker.oscog-eem.2338
> Author: eem
> Time: 22 February 2018, 10:25:17.794166 am
> UUID: 1672c678-41b4-41f2-a061-e201562fc75c
> Ancestors: VMMaker.oscog-eem.2337
>
> Fix a slip in primitiveDecompressFromByteArray caught by IncludedMethodsTests.  Thank you David!
>
> =============== Diff against VMMaker.oscog-eem.2337 ===============
>
> Item was changed:
>  ----- Method: MiscPrimitivePlugin>>primitiveDecompressFromByteArray (in category 'primitives') -----
>  primitiveDecompressFromByteArray
>   "Bitmap decompress: bm fromByteArray: ba at: index"
>   <export: true>
>   | bm ba index i anInt code data end k n pastEnd |
>   <var: 'ba' type: #'unsigned char *'>
>   <var: 'bm' type: #'int *'>
>   <var: 'anInt' type: #'unsigned int'>
>   <var: 'code' type: #'unsigned int'>
>   <var: 'data' type: #'unsigned int'>
>   <var: 'n' type: #'unsigned int'>

Shouldn't i be declared as unsigned int too? It's used for indexing.

>   bm := self cCode: [interpreterProxy arrayValueOf: (interpreterProxy stackValue: 2)]
>   inSmalltalk: [interpreterProxy
>   cCoerce: (interpreterProxy arrayValueOf: (interpreterProxy stackValue: 2))
>   to: #'int *'].
>   (interpreterProxy isOopImmutable: (interpreterProxy stackValue: 2)) ifTrue:
>   [^interpreterProxy primitiveFailFor: PrimErrNoModification].
>   (interpreterProxy isBytes: (interpreterProxy stackValue: 1)) ifFalse: [^interpreterProxy primitiveFail].
>   ba := interpreterProxy firstIndexableField: (interpreterProxy stackValue: 1).
>   index := interpreterProxy stackIntegerValue: 0.

Can index be negative or 0? If yes, then the value of i will be negative
(unless it's implicit type is unsigned) and that will result in out of
bounds indexing into ba a few lines below here.

>   interpreterProxy failed ifTrue: [^nil].
>   i := index - 1.
>   k := 0.
>   end := interpreterProxy sizeOfSTArrayFromCPrimitive: ba.
>   pastEnd := interpreterProxy sizeOfSTArrayFromCPrimitive: bm.
>   [i < end] whileTrue:
>   [anInt := ba at: i.
>   i := i + 1.
>   anInt <= 223 ifFalse:
>   [anInt <= 254
>   ifTrue:
>   [anInt := anInt - 224 * 256 + (ba at: i).

I would use bitShift: 8 instead of * 256, just to be consistent with the
rest of the method.

>   i := i + 1]
>   ifFalse:
>   [anInt := 0.
>   1 to: 4 by: 1 do:
>   [ :j | anInt := (anInt bitShift: 8) + (ba at: i).
>   i := i + 1]]].
>   n := anInt >> 2.
> + k + n > pastEnd ifTrue: [^interpreterProxy primitiveFail].
> - k + n >= pastEnd ifTrue: [^interpreterProxy primitiveFail].
>   code := anInt bitAnd: 3.
>   "code = 0 ifTrue: [nil]."
>   code = 1 ifTrue:
>   [data := ba at: i.
>   i := i + 1.
>   data := data bitOr: (data bitShift: 8).
>   data := data bitOr: (data bitShift: 16).

I don't know what the point of this part of the code is, but I think the
above 4 lines could read:

[data := 16r10101 * (ba at: i).
i := i + 1.

Levente

>   1 to: n do:
>   [ :j |
>   bm at: k put: data.
>   k := k + 1]].
>   code = 2 ifTrue:
>   [data := 0.
>   1 to: 4 do:
>   [ :j |
>   data := (data bitShift: 8) bitOr: (ba at: i).
>   i := i + 1].
>   1 to: n do:
>   [ :j |
>   bm at: k put: data.
>   k := k + 1]].
>   code = 3 ifTrue:
>   [1 to: n do:
>   [ :m |
>   data := 0.
>   1 to: 4 do:
>   [ :j |
>   data := (data bitShift: 8) bitOr: (ba at: i).
>   i := i + 1].
>   bm at: k put: data.
>   k := k + 1]]].
>   interpreterProxy pop: interpreterProxy methodArgumentCount!
Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-eem.2338.mcz

Eliot Miranda-2
 
Hi Levente,

    I really appreciate you taking a look.  I will say that the rewrite tried the stay as close to the originals while changing 1-relative indexing to 0-relative.  But I think we can also improve on the originals.  Indeed I spotted and fixed a potential bounds violation in primitiveConvert8Bit that only checked the size of one of the two array arguments.

So can I ask you to read the primitives in the previous commit too?  Let's polish these a little :-)

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

> On Feb 22, 2018, at 3:14 PM, Levente Uzonyi <[hidden email]> wrote:
>
> Just had a look at this snippet, and wrote some quick inline comments.
>
>> On Thu, 22 Feb 2018, [hidden email] wrote:
>>
>> Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
>> http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2338.mcz
>>
>> ==================== Summary ====================
>>
>> Name: VMMaker.oscog-eem.2338
>> Author: eem
>> Time: 22 February 2018, 10:25:17.794166 am
>> UUID: 1672c678-41b4-41f2-a061-e201562fc75c
>> Ancestors: VMMaker.oscog-eem.2337
>>
>> Fix a slip in primitiveDecompressFromByteArray caught by IncludedMethodsTests.  Thank you David!
>>
>> =============== Diff against VMMaker.oscog-eem.2337 ===============
>>
>> Item was changed:
>> ----- Method: MiscPrimitivePlugin>>primitiveDecompressFromByteArray (in category 'primitives') -----
>> primitiveDecompressFromByteArray
>>    "Bitmap decompress: bm fromByteArray: ba at: index"
>>    <export: true>
>>    | bm ba index i anInt code data end k n pastEnd |
>>    <var: 'ba' type: #'unsigned char *'>
>>    <var: 'bm' type: #'int *'>
>>    <var: 'anInt' type: #'unsigned int'>
>>    <var: 'code' type: #'unsigned int'>
>>    <var: 'data' type: #'unsigned int'>
>>    <var: 'n' type: #'unsigned int'>
>
> Shouldn't i be declared as unsigned int too? It's used for indexing.
>
>>    bm := self cCode: [interpreterProxy arrayValueOf: (interpreterProxy stackValue: 2)]
>>                inSmalltalk: [interpreterProxy
>>                                cCoerce: (interpreterProxy arrayValueOf: (interpreterProxy stackValue: 2))
>>                                to: #'int *'].
>>    (interpreterProxy isOopImmutable: (interpreterProxy stackValue: 2)) ifTrue:
>>        [^interpreterProxy primitiveFailFor: PrimErrNoModification].
>>    (interpreterProxy isBytes: (interpreterProxy stackValue: 1)) ifFalse: [^interpreterProxy primitiveFail].
>>    ba := interpreterProxy firstIndexableField: (interpreterProxy stackValue: 1).
>>    index := interpreterProxy stackIntegerValue: 0.
>
> Can index be negative or 0? If yes, then the value of i will be negative (unless it's implicit type is unsigned) and that will result in out of bounds indexing into ba a few lines below here.
>
>>    interpreterProxy failed ifTrue: [^nil].
>>    i := index - 1.
>>    k := 0.
>>    end := interpreterProxy sizeOfSTArrayFromCPrimitive: ba.
>>    pastEnd := interpreterProxy sizeOfSTArrayFromCPrimitive: bm.
>>    [i < end] whileTrue:
>>        [anInt := ba at: i.
>>        i := i + 1.
>>        anInt <= 223 ifFalse:
>>            [anInt <= 254
>>                ifTrue:
>>                    [anInt := anInt - 224 * 256 + (ba at: i).
>
> I would use bitShift: 8 instead of * 256, just to be consistent with the rest of the method.
>
>>                    i := i + 1]
>>                ifFalse:
>>                    [anInt := 0.
>>                    1 to: 4 by: 1 do:
>>                        [ :j | anInt := (anInt bitShift: 8) + (ba at: i).
>>                        i := i + 1]]].
>>        n := anInt >> 2.
>> +        k + n > pastEnd ifTrue: [^interpreterProxy primitiveFail].
>> -        k + n >= pastEnd ifTrue: [^interpreterProxy primitiveFail].
>>        code := anInt bitAnd: 3.
>>        "code = 0 ifTrue: [nil]."
>>        code = 1 ifTrue:
>>            [data := ba at: i.
>>            i := i + 1.
>>            data := data bitOr: (data bitShift: 8).
>>            data := data bitOr: (data bitShift: 16).
>
> I don't know what the point of this part of the code is, but I think the above 4 lines could read:
>
> [data := 16r10101 * (ba at: i).
> i := i + 1.
>
> Levente
>
>>            1 to: n do:
>>                [ :j |
>>                bm at: k put: data.
>>                k := k + 1]].
>>        code = 2 ifTrue:
>>            [data := 0.
>>            1 to: 4 do:
>>                [ :j |
>>                data := (data bitShift: 8) bitOr: (ba at: i).
>>                i := i + 1].
>>            1 to: n do:
>>                [ :j |
>>                bm at: k put: data.
>>                k := k + 1]].
>>        code = 3 ifTrue:
>>            [1 to: n do:
>>                [ :m |
>>                data := 0.
>>                1 to: 4 do:
>>                    [ :j |
>>                    data := (data bitShift: 8) bitOr: (ba at: i).
>>                    i := i + 1].
>>                bm at: k put: data.
>>                k := k + 1]]].
>>    interpreterProxy pop: interpreterProxy methodArgumentCount!
Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-eem.2338.mcz

Levente Uzonyi
 
Hi Eliot,

I went through the primitives and found the following issues:

primitiveCompareString
- size of the order variable should be checked to be 256 as it is done in primitiveFindFirstInString
primitiveCompressToByteArray
- ba should be bounds checked
- bm is int*, but it probably should be unsigned int* because of the right shifts
primitiveDecompressFromByteArray
- bm is int*, but it should probably be unsigned int* as the method stores unsigned ints (data) into it
- index should be bounds checked (1 .. end)
- i, k, end and pastEnd should be unsigned int
primitiveFindFirstInString
- inclustionMap should be unsigned char* (in practice it's a ByteArray with 0-1 values)
primitiveIndexOfAsciiInString
- start can be 0 or negative. Either the loop should start from (start - 1 max: 0) or there should be an error if start is 0 or negative
- anInteger should be bounds checked (0 .. 255)
primitiveStringHash
- speciesHash should probably be unsigned int
primitiveTranslateStringWithTable
- start and stop need bounds checks (0 .. aString size - 1)
- the size of table should be checked to be 256

Levente

On Thu, 22 Feb 2018, Eliot Miranda wrote:

>
> Hi Levente,
>
>    I really appreciate you taking a look.  I will say that the rewrite tried the stay as close to the originals while changing 1-relative indexing to 0-relative.  But I think we can also improve on the originals.  Indeed I spotted and fixed a potential bounds violation in primitiveConvert8Bit that only checked the size of one of the two array arguments.
>
> So can I ask you to read the primitives in the previous commit too?  Let's polish these a little :-)
>
> _,,,^..^,,,_ (phone)
>
>> On Feb 22, 2018, at 3:14 PM, Levente Uzonyi <[hidden email]> wrote:
>>
>> Just had a look at this snippet, and wrote some quick inline comments.
>>
>>> On Thu, 22 Feb 2018, [hidden email] wrote:
>>>
>>> Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
>>> http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2338.mcz
>>>
>>> ==================== Summary ====================
>>>
>>> Name: VMMaker.oscog-eem.2338
>>> Author: eem
>>> Time: 22 February 2018, 10:25:17.794166 am
>>> UUID: 1672c678-41b4-41f2-a061-e201562fc75c
>>> Ancestors: VMMaker.oscog-eem.2337
>>>
>>> Fix a slip in primitiveDecompressFromByteArray caught by IncludedMethodsTests.  Thank you David!
>>>
>>> =============== Diff against VMMaker.oscog-eem.2337 ===============
>>>
>>> Item was changed:
>>> ----- Method: MiscPrimitivePlugin>>primitiveDecompressFromByteArray (in category 'primitives') -----
>>> primitiveDecompressFromByteArray
>>>    "Bitmap decompress: bm fromByteArray: ba at: index"
>>>    <export: true>
>>>    | bm ba index i anInt code data end k n pastEnd |
>>>    <var: 'ba' type: #'unsigned char *'>
>>>    <var: 'bm' type: #'int *'>
>>>    <var: 'anInt' type: #'unsigned int'>
>>>    <var: 'code' type: #'unsigned int'>
>>>    <var: 'data' type: #'unsigned int'>
>>>    <var: 'n' type: #'unsigned int'>
>>
>> Shouldn't i be declared as unsigned int too? It's used for indexing.
>>
>>>    bm := self cCode: [interpreterProxy arrayValueOf: (interpreterProxy stackValue: 2)]
>>>                inSmalltalk: [interpreterProxy
>>>                                cCoerce: (interpreterProxy arrayValueOf: (interpreterProxy stackValue: 2))
>>>                                to: #'int *'].
>>>    (interpreterProxy isOopImmutable: (interpreterProxy stackValue: 2)) ifTrue:
>>>        [^interpreterProxy primitiveFailFor: PrimErrNoModification].
>>>    (interpreterProxy isBytes: (interpreterProxy stackValue: 1)) ifFalse: [^interpreterProxy primitiveFail].
>>>    ba := interpreterProxy firstIndexableField: (interpreterProxy stackValue: 1).
>>>    index := interpreterProxy stackIntegerValue: 0.
>>
>> Can index be negative or 0? If yes, then the value of i will be negative (unless it's implicit type is unsigned) and that will result in out of bounds indexing into ba a few lines below here.
>>
>>>    interpreterProxy failed ifTrue: [^nil].
>>>    i := index - 1.
>>>    k := 0.
>>>    end := interpreterProxy sizeOfSTArrayFromCPrimitive: ba.
>>>    pastEnd := interpreterProxy sizeOfSTArrayFromCPrimitive: bm.
>>>    [i < end] whileTrue:
>>>        [anInt := ba at: i.
>>>        i := i + 1.
>>>        anInt <= 223 ifFalse:
>>>            [anInt <= 254
>>>                ifTrue:
>>>                    [anInt := anInt - 224 * 256 + (ba at: i).
>>
>> I would use bitShift: 8 instead of * 256, just to be consistent with the rest of the method.
>>
>>>                    i := i + 1]
>>>                ifFalse:
>>>                    [anInt := 0.
>>>                    1 to: 4 by: 1 do:
>>>                        [ :j | anInt := (anInt bitShift: 8) + (ba at: i).
>>>                        i := i + 1]]].
>>>        n := anInt >> 2.
>>> +        k + n > pastEnd ifTrue: [^interpreterProxy primitiveFail].
>>> -        k + n >= pastEnd ifTrue: [^interpreterProxy primitiveFail].
>>>        code := anInt bitAnd: 3.
>>>        "code = 0 ifTrue: [nil]."
>>>        code = 1 ifTrue:
>>>            [data := ba at: i.
>>>            i := i + 1.
>>>            data := data bitOr: (data bitShift: 8).
>>>            data := data bitOr: (data bitShift: 16).
>>
>> I don't know what the point of this part of the code is, but I think the above 4 lines could read:
>>
>> [data := 16r10101 * (ba at: i).
>> i := i + 1.
>>
>> Levente
>>
>>>            1 to: n do:
>>>                [ :j |
>>>                bm at: k put: data.
>>>                k := k + 1]].
>>>        code = 2 ifTrue:
>>>            [data := 0.
>>>            1 to: 4 do:
>>>                [ :j |
>>>                data := (data bitShift: 8) bitOr: (ba at: i).
>>>                i := i + 1].
>>>            1 to: n do:
>>>                [ :j |
>>>                bm at: k put: data.
>>>                k := k + 1]].
>>>        code = 3 ifTrue:
>>>            [1 to: n do:
>>>                [ :m |
>>>                data := 0.
>>>                1 to: 4 do:
>>>                    [ :j |
>>>                    data := (data bitShift: 8) bitOr: (ba at: i).
>>>                    i := i + 1].
>>>                bm at: k put: data.
>>>                k := k + 1]]].
>>>    interpreterProxy pop: interpreterProxy methodArgumentCount!
Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-eem.2338.mcz

Eliot Miranda-2
 
Hi Levente,

[I'm sorry, I apparently forgot to hit send some weeks ago]

On Sun, Feb 25, 2018 at 4:12 PM, Levente Uzonyi <[hidden email]> wrote:

Hi Eliot,

I went through the primitives and found the following issues:

Thanks for these!  I've fixed most of them. Justification for the unchanged ones below.  Feel free to twist my arm if any still look wrong :-)

 

primitiveCompareString
- size of the order variable should be checked to be 256 as it is done in primitiveFindFirstInString
primitiveCompressToByteArray
- ba should be bounds checked
- bm is int*, but it probably should be unsigned int* because of the right shifts
primitiveDecompressFromByteArray
- bm is int*, but it should probably be unsigned int* as the method stores unsigned ints (data) into it
- index should be bounds checked (1 .. end)

It gets checked anyway with the comparison against pastEnd
 
- i, k, end and pastEnd should be unsigned int

That's OK.  In neither V3 nor Spur can objects have more than 1Gb fields so in practice indices can never go negative.
 
primitiveFindFirstInString
- inclustionMap should be unsigned char* (in practice it's a ByteArray with 0-1 values)

Since its bytes only get tested for 0 I left this unchanged.
 
primitiveIndexOfAsciiInString
- start can be 0 or negative. Either the loop should start from (start - 1 max: 0) or there should be an error if start is 0 or negative
- anInteger should be bounds checked (0 .. 255)

Not sure about this.  It is a waste of time to check, but if one givers it an out-of-bound value the result will still be valid, and if the primitive failed it would be no better.  So I left it alone.
 
primitiveStringHash
- speciesHash should probably be unsigned int

Again cuz of the masking its ok to leave this.
 
primitiveTranslateStringWithTable
- start and stop need bounds checks (0 .. aString size - 1)
- the size of table should be checked to be 256

Levente


On Thu, 22 Feb 2018, Eliot Miranda wrote:


Hi Levente,

   I really appreciate you taking a look.  I will say that the rewrite tried the stay as close to the originals while changing 1-relative indexing to 0-relative.  But I think we can also improve on the originals.  Indeed I spotted and fixed a potential bounds violation in primitiveConvert8Bit that only checked the size of one of the two array arguments.

So can I ask you to read the primitives in the previous commit too?  Let's polish these a little :-)

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

On Feb 22, 2018, at 3:14 PM, Levente Uzonyi <[hidden email]> wrote:

Just had a look at this snippet, and wrote some quick inline comments.

On Thu, 22 Feb 2018, [hidden email] wrote:

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

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

Name: VMMaker.oscog-eem.2338
Author: eem
Time: 22 February 2018, 10:25:17.794166 am
UUID: 1672c678-41b4-41f2-a061-e201562fc75c
Ancestors: VMMaker.oscog-eem.2337

Fix a slip in primitiveDecompressFromByteArray caught by IncludedMethodsTests.  Thank you David!

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

Item was changed:
----- Method: MiscPrimitivePlugin>>primitiveDecompressFromByteArray (in category 'primitives') -----
primitiveDecompressFromByteArray
   "Bitmap decompress: bm fromByteArray: ba at: index"
   <export: true>
   | bm ba index i anInt code data end k n pastEnd |
   <var: 'ba' type: #'unsigned char *'>
   <var: 'bm' type: #'int *'>
   <var: 'anInt' type: #'unsigned int'>
   <var: 'code' type: #'unsigned int'>
   <var: 'data' type: #'unsigned int'>
   <var: 'n' type: #'unsigned int'>

Shouldn't i be declared as unsigned int too? It's used for indexing.

   bm := self cCode: [interpreterProxy arrayValueOf: (interpreterProxy stackValue: 2)]
               inSmalltalk: [interpreterProxy
                               cCoerce: (interpreterProxy arrayValueOf: (interpreterProxy stackValue: 2))
                               to: #'int *'].
   (interpreterProxy isOopImmutable: (interpreterProxy stackValue: 2)) ifTrue:
       [^interpreterProxy primitiveFailFor: PrimErrNoModification].
   (interpreterProxy isBytes: (interpreterProxy stackValue: 1)) ifFalse: [^interpreterProxy primitiveFail].
   ba := interpreterProxy firstIndexableField: (interpreterProxy stackValue: 1).
   index := interpreterProxy stackIntegerValue: 0.

Can index be negative or 0? If yes, then the value of i will be negative (unless it's implicit type is unsigned) and that will result in out of bounds indexing into ba a few lines below here.

   interpreterProxy failed ifTrue: [^nil].
   i := index - 1.
   k := 0.
   end := interpreterProxy sizeOfSTArrayFromCPrimitive: ba.
   pastEnd := interpreterProxy sizeOfSTArrayFromCPrimitive: bm.
   [i < end] whileTrue:
       [anInt := ba at: i.
       i := i + 1.
       anInt <= 223 ifFalse:
           [anInt <= 254
               ifTrue:
                   [anInt := anInt - 224 * 256 + (ba at: i).

I would use bitShift: 8 instead of * 256, just to be consistent with the rest of the method.

                   i := i + 1]
               ifFalse:
                   [anInt := 0.
                   1 to: 4 by: 1 do:
                       [ :j | anInt := (anInt bitShift: 8) + (ba at: i).
                       i := i + 1]]].
       n := anInt >> 2.
+        k + n > pastEnd ifTrue: [^interpreterProxy primitiveFail].
-        k + n >= pastEnd ifTrue: [^interpreterProxy primitiveFail].
       code := anInt bitAnd: 3.
       "code = 0 ifTrue: [nil]."
       code = 1 ifTrue:
           [data := ba at: i.
           i := i + 1.
           data := data bitOr: (data bitShift: 8).
           data := data bitOr: (data bitShift: 16).

I don't know what the point of this part of the code is, but I think the above 4 lines could read:

[data := 16r10101 * (ba at: i).
i := i + 1.

Levente

           1 to: n do:
               [ :j |
               bm at: k put: data.
               k := k + 1]].
       code = 2 ifTrue:
           [data := 0.
           1 to: 4 do:
               [ :j |
               data := (data bitShift: 8) bitOr: (ba at: i).
               i := i + 1].
           1 to: n do:
               [ :j |
               bm at: k put: data.
               k := k + 1]].
       code = 3 ifTrue:
           [1 to: n do:
               [ :m |
               data := 0.
               1 to: 4 do:
                   [ :j |
                   data := (data bitShift: 8) bitOr: (ba at: i).
                   i := i + 1].
               bm at: k put: data.
               k := k + 1]]].
   interpreterProxy pop: interpreterProxy methodArgumentCount!



--
_,,,^..^,,,_
best, Eliot
Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-eem.2338.mcz

Levente Uzonyi
 
Hi Eliot,

On Thu, 12 Apr 2018, Eliot Miranda wrote:

> [I'm sorry, I apparently forgot to hit send some weeks ago]

Well, I had started to rewrite the methods myself along with adding tests,
but you were quicker and pushed the changes.
I think there are still things that should be fixed. When time allows,
I'll check my tests and merge them with the existing
MiscPrimitivePluginTest.

>> primitiveDecompressFromByteArray
>> - bm is int*, but it should probably be unsigned int* as the method
stores unsigned ints (data) into it
>> - index should be bounds checked (1 .. end)
>
> It gets checked anyway with the comparison against pastEnd

Unfortunately that's not the case. i is compared to end, not pastEnd.
If index, which is an unnecessary variable btw, is less than or equal to
0, then the value of i will be negative, and the input will be processed
no matter what the value of end is, hence random data from memory will be
read and processed:

Smalltalk garbageCollect.
ba := ByteArray new: 256.
bm := Bitmap new: 1024.
passes := OrderedCollection new.
success := true.
[
  0 to: -1000000 by: -1 do: [ :start |
  success := true.
  bm decompress: bm fromByteArray: ba at: start.
  success ifTrue: [ passes add: start ] ] ]
  on: Error
  do: [ :error |
  success := false.
  error return: nil ].
passes

>> - i, k, end and pastEnd should be unsigned int
>
> That's OK.  In neither V3 nor Spur can objects have more than 1Gb fields so in practice indices can never go negative.

If i's type were unsigned int, the above code wouldn't work, because i < end would be false.

Levente
Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-eem.2338.mcz

Eliot Miranda-2
 


On Sat, Apr 14, 2018 at 10:47 AM, Levente Uzonyi <[hidden email]> wrote:

Hi Eliot,

On Thu, 12 Apr 2018, Eliot Miranda wrote:

[I'm sorry, I apparently forgot to hit send some weeks ago]

Well, I had started to rewrite the methods myself along with adding tests, but you were quicker and pushed the changes.
I think there are still things that should be fixed. When time allows, I'll check my tests and merge them with the existing MiscPrimitivePluginTest.

thanks, man!
 


primitiveDecompressFromByteArray
- bm is int*, but it should probably be unsigned int* as the method
stores unsigned ints (data) into it
- index should be bounds checked (1 .. end)

It gets checked anyway with the comparison against pastEnd

Unfortunately that's not the case. i is compared to end, not pastEnd.
If index, which is an unnecessary variable btw, is less than or equal to 0, then the value of i will be negative, and the input will be processed no matter what the value of end is, hence random data from memory will be read and processed:

Smalltalk garbageCollect.
ba := ByteArray new: 256.
bm := Bitmap new: 1024.
passes := OrderedCollection new.
success := true.
[
        0 to: -1000000 by: -1 do: [ :start |
                success := true.
                bm decompress: bm fromByteArray: ba at: start.
                success ifTrue: [ passes add: start ] ] ]
        on: Error
        do: [ :error |
                success := false.
                error return: nil ].
passes

- i, k, end and pastEnd should be unsigned int

That's OK.  In neither V3 nor Spur can objects have more than 1Gb fields so in practice indices can never go negative.

If i's type were unsigned int, the above code wouldn't work, because i < end would be false.

Levente



--
_,,,^..^,,,_
best, Eliot