Integer overflow with BitBlt rule 20 and depth 32

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

Integer overflow with BitBlt rule 20 and depth 32

Henrik Sperre Johansen
 
Any combination of alpha values with a  sum greater than 383 will  
cause an overflow, and return an alpha of sum - 255.

Works correctly in BitBltSimulator, but the generated x86 C-code fails.

Reproduced on latest versions of both Windows and MacOSX VMs. (I don't  
have a Linux install)
Not quite sure of the best way to fix this (and possibly other  
similarily effected rules when depth is 32)

Cheers,
Henry

Tests:

sourceForm destForm blt|
destForm := Form extent: 1@1 depth: 32.
destForm  bits at: 1 put: ((192 << 24) + (255 << 16) + (255 << 8) +  
255).
sourceForm := Form extent: 1@1 depth: 32.
sourceForm bits at: 1 put: ((192 << 24) + (33 << 16) + (25 << 8) + 27).
blt := BitBlt new.
blt sourceForm: sourceForm.
blt sourceOrigin: 0@0.
blt setDestForm: destForm.
blt destOrigin: 0@0.
blt combinationRule: 20.
blt copyBits.
((blt destForm bits at: 1) digitAt: 4) = 255

- Using Simulator:
|word1 word2|
word1 := (192 << 24) + (255 << 16) + (255 << 8) + 255.
word2 := (192 << 24) + (33 << 16) + (25 << 8) + 27.
((BitBltSimulator new initBBOpTable partitionedAdd: word1 to: word2  
nBits: 8
nPartitions: 4) digitAt: 4) = 255
Reply | Threaded
Open this post in threaded view
|

Re: Integer overflow with BitBlt rule 20 and depth 32

David T. Lewis
 
Could this be the cause of issue for which Juan was asking help?

  Subject line "[Vm-dev] Bug in BitBlt. Need Help."
  http://lists.squeakfoundation.org/pipermail/vm-dev/2009-September/003160.html


On Tue, Oct 20, 2009 at 12:24:22AM +0200, Henrik Johansen wrote:

>
> Any combination of alpha values with a  sum greater than 383 will  
> cause an overflow, and return an alpha of sum - 255.
>
> Works correctly in BitBltSimulator, but the generated x86 C-code fails.
>
> Reproduced on latest versions of both Windows and MacOSX VMs. (I don't  
> have a Linux install)
> Not quite sure of the best way to fix this (and possibly other  
> similarily effected rules when depth is 32)
>
> Cheers,
> Henry
>
> Tests:
>
> sourceForm destForm blt|
> destForm := Form extent: 1@1 depth: 32.
> destForm  bits at: 1 put: ((192 << 24) + (255 << 16) + (255 << 8) +  
> 255).
> sourceForm := Form extent: 1@1 depth: 32.
> sourceForm bits at: 1 put: ((192 << 24) + (33 << 16) + (25 << 8) + 27).
> blt := BitBlt new.
> blt sourceForm: sourceForm.
> blt sourceOrigin: 0@0.
> blt setDestForm: destForm.
> blt destOrigin: 0@0.
> blt combinationRule: 20.
> blt copyBits.
> ((blt destForm bits at: 1) digitAt: 4) = 255
>
> - Using Simulator:
> |word1 word2|
> word1 := (192 << 24) + (255 << 16) + (255 << 8) + 255.
> word2 := (192 << 24) + (33 << 16) + (25 << 8) + 27.
> ((BitBltSimulator new initBBOpTable partitionedAdd: word1 to: word2  
> nBits: 8
> nPartitions: 4) digitAt: 4) = 255
Reply | Threaded
Open this post in threaded view
|

Re: Integer overflow with BitBlt rule 20 and depth 32

Henrik Sperre Johansen
 
On 20.10.2009 15:56, David T. Lewis wrote:
>
> Could this be the cause of issue for which Juan was asking help?
>
>    Subject line "[Vm-dev] Bug in BitBlt. Need Help."
>    http://lists.squeakfoundation.org/pipermail/vm-dev/2009-September/003160.html
>    
Yes, that's exactly it, sorry I had not seen it.
Attached is a proof-of-concept fix (for partitionedAdd: only), valid as
long as nParts > 1 ( I suggest one wouldn't use partitionedAdd anyways
if it were :) )
If anyone has a better idea, it'd be appreciated!

Correctness test:
| sourceForm destForm blt correctAlphas |
     correctAlphas := 0.
     0  to: 255 do: [:sourceAlpha |
         sourceForm := Form extent: 1 @ 1 depth: 32.
         sourceForm bits at: 1 put: sourceAlpha << 24 + (33 << 16) + (25
<< 8) + 27.
         0 to: 255 do: [:destAlpha |
             destForm := Form extent: 1 @ 1 depth: 32.
             destForm bits at: 1 put: destAlpha << 24 + (255 << 16) +
(255 << 8) + 255.
              blt := BitBlt new.
              blt sourceForm: sourceForm.
              blt sourceOrigin: 0 @ 0.
              blt setDestForm: destForm.
              blt destOrigin: 0 @ 0.
              blt combinationRule: 20.
              blt copyBits.
              correctAlphas := correctAlphas
                + (((blt destForm bits at: 1) digitAt: 4) = (destAlpha +
sourceAlpha min: 255)
                         ifTrue: [1]
                         ifFalse: [0])
      ]].
     self assert: 65536 equals: correctAlphas

Performance is not impacted to a significant degree as far as I can
tell, the from runtimes of the test:
[|sourceForm destForm blt|
destForm := Form extent: 99@99 depth: 32.
1 to: destForm bits size do: [:ix |
destForm  bits at: ix put: ((192 << 24) + (255 << 16) + (255 << 8) + 255).].
sourceForm := Form extent: 99@99 depth: 32.
1 to: sourceForm bits size do: [:ix |
sourceForm bits at: ix put: ((192 << 24) + (33 << 16) + (25 << 8) + 27).].
blt := BitBlt new.
blt sourceForm: sourceForm.
blt sourceOrigin: 0@0.
blt setDestForm: destForm.
blt destOrigin: 0@0.
blt combinationRule: 20.
5000 timesRepeat: [
blt copyBits.]] timeToRun

Cheers,
Henry

BitBltSimulation-partitionedAddtonBitsnPartitions.st (1K) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: Integer overflow with BitBlt rule 20 and depth 32

Juan Vuletich-4
 
Hi Folks,

Looking in detail I found two issues here. One is that the addition can
silently overflow. The other one is that in the generated C code ALL the
variables (arguments and temporaries) are int and not unsigned. (BTW,
this is for sure affecting other rules, not only rgbAdd.) If we fixed
the int issue, then much simpler (and a bit faster) code would work:

partitionedAdd: word1 to: word2 nBits: nBits nPartitions: nParts
    "Add word1 to word2 as nParts partitions of nBits each.
    This is useful for packed pixels, or packed colors"
    | mask sum result maskedWord1 |
    mask := maskTable at: nBits.  "partition mask starts at the right"
    result := 0.
    1 to: nParts do: [ :i |
        maskedWord1 _ word1 bitAnd: mask.
        sum := maskedWord1 + (word2 bitAnd: mask).
        (sum <= mask  "result must not carry out of partition"
                    and: [ sum >= maskedWord1 ])                      
            "**** This is the only change ****"    
            ifTrue: [result := result bitOr: sum]
            ifFalse: [result := result bitOr: mask].
        mask := mask << nBits  "slide left to next partition"].
    ^ result

I believe we need to add explicit declarations of all variables being
unsigned. Or perhaps enhance a bit the code generator, by allowing a
plugin to declare its default numeric type. For BitBlt it could be
unsigned. For DSP stuff it could be float or double, making the Slang
code much nicer by not needing all the explicit type declarations. What
do you think?

Cheers,
Juan Vuletich

Henrik Sperre Johansen wrote:

>  
>
> ------------------------------------------------------------------------
>
> On 20.10.2009 15:56, David T. Lewis wrote:
>>
>> Could this be the cause of issue for which Juan was asking help?
>>
>>    Subject line "[Vm-dev] Bug in BitBlt. Need Help."
>>    
>> http://lists.squeakfoundation.org/pipermail/vm-dev/2009-September/003160.html 
>>
>>    
> Yes, that's exactly it, sorry I had not seen it.
> Attached is a proof-of-concept fix (for partitionedAdd: only), valid
> as long as nParts > 1 ( I suggest one wouldn't use partitionedAdd
> anyways if it were :) )
> If anyone has a better idea, it'd be appreciated!
>
> Correctness test:
> | sourceForm destForm blt correctAlphas |
>     correctAlphas := 0.
>     0  to: 255 do: [:sourceAlpha |
>         sourceForm := Form extent: 1 @ 1 depth: 32.
>         sourceForm bits at: 1 put: sourceAlpha << 24 + (33 << 16) +
> (25 << 8) + 27.
>         0 to: 255 do: [:destAlpha |
>             destForm := Form extent: 1 @ 1 depth: 32.
>             destForm bits at: 1 put: destAlpha << 24 + (255 << 16) +
> (255 << 8) + 255.
>              blt := BitBlt new.
>              blt sourceForm: sourceForm.
>              blt sourceOrigin: 0 @ 0.
>              blt setDestForm: destForm.
>              blt destOrigin: 0 @ 0.
>              blt combinationRule: 20.
>              blt copyBits.
>              correctAlphas := correctAlphas
>                + (((blt destForm bits at: 1) digitAt: 4) = (destAlpha
> + sourceAlpha min: 255)
>                         ifTrue: [1]
>                         ifFalse: [0])
>      ]].
>     self assert: 65536 equals: correctAlphas
>
> Performance is not impacted to a significant degree as far as I can
> tell, the from runtimes of the test:
> [|sourceForm destForm blt|
> destForm := Form extent: 99@99 depth: 32.
> 1 to: destForm bits size do: [:ix |
> destForm  bits at: ix put: ((192 << 24) + (255 << 16) + (255 << 8) +
> 255).].
> sourceForm := Form extent: 99@99 depth: 32.
> 1 to: sourceForm bits size do: [:ix |
> sourceForm bits at: ix put: ((192 << 24) + (33 << 16) + (25 << 8) +
> 27).].
> blt := BitBlt new.
> blt sourceForm: sourceForm.
> blt sourceOrigin: 0@0.
> blt setDestForm: destForm.
> blt destOrigin: 0@0.
> blt combinationRule: 20.
> 5000 timesRepeat: [
> blt copyBits.]] timeToRun
>
> Cheers,
> Henry
> ------------------------------------------------------------------------
>
>
> No virus found in this incoming message.
> Checked by AVG - www.avg.com
> Version: 8.5.423 / Virus Database: 270.14.26/2451 - Release Date: 10/22/09 08:51:00
>

Reply | Threaded
Open this post in threaded view
|

Re: Integer overflow with BitBlt rule 20 and depth 32

David T. Lewis
 
On Thu, Oct 22, 2009 at 11:15:30AM -0300, Juan Vuletich wrote:
>
> I believe we need to add explicit declarations of all variables being
> unsigned. Or perhaps enhance a bit the code generator, by allowing a
> plugin to declare its default numeric type. For BitBlt it could be
> unsigned. For DSP stuff it could be float or double, making the Slang
> code much nicer by not needing all the explicit type declarations. What
> do you think?

For most plugins, adding the explicit declarations for variables and
method returns is sufficient, and takes care of the problem very well.
For BitBlt it looks like it would be a lot of very tedious work. Does
anyone have a code generator enhancement that would implement the
default numeric type idea?

The current default data type of sqInt is safe to use for object
references for both 32 bit and 64 bit object memory. An implementation
of default numeric types for plugins would need to be careful about
method return declarations. If a method returns an object reference,
it cannot be declared as int or long.

If the goal is to fix issues in BitBlt, my guess is that the fastest
way to get this done is to just grind through it and do all of the
explicit type declarations for variables and method returns. It would
take a few hours to do the work, but once it's done it's done.

Dave
 
Reply | Threaded
Open this post in threaded view
|

Re: Integer overflow with BitBlt rule 20 and depth 32

Juan Vuletich-4
 
Hi Folks,

David T. Lewis wrote:

>  
> On Thu, Oct 22, 2009 at 11:15:30AM -0300, Juan Vuletich wrote:
>  
>> I believe we need to add explicit declarations of all variables being
>> unsigned. Or perhaps enhance a bit the code generator, by allowing a
>> plugin to declare its default numeric type. For BitBlt it could be
>> unsigned. For DSP stuff it could be float or double, making the Slang
>> code much nicer by not needing all the explicit type declarations. What
>> do you think?
>>    
>
> For most plugins, adding the explicit declarations for variables and
> method returns is sufficient, and takes care of the problem very well.
> For BitBlt it looks like it would be a lot of very tedious work. Does
> anyone have a code generator enhancement that would implement the
> default numeric type idea?
>
> The current default data type of sqInt is safe to use for object
> references for both 32 bit and 64 bit object memory. An implementation
> of default numeric types for plugins would need to be careful about
> method return declarations. If a method returns an object reference,
> it cannot be declared as int or long.
>
> If the goal is to fix issues in BitBlt, my guess is that the fastest
> way to get this done is to just grind through it and do all of the
> explicit type declarations for variables and method returns. It would
> take a few hours to do the work, but once it's done it's done.
>
> Dave
Ok. This is my first try at this. I went back to my old 6809 assembly
language book to remember by 2's complement aritmethic. The bit pattern
of the result of addition and substraction is not altered by considering
a number signed or unsigned. The only operations that are affected are
multiplication and comparisons. rgbMul works ok because it will never
use the most significant bit (the sign bit). So I added the correct
types only on those operations that needed to do correct comparisons. I
also added the check for overflow in rgbAdd (the only place where it is
needed).

I'm not sure if we should add the types everywhere, or it is ok to add
them just to a few functions as I did. I'm running out of time today,
anybody who can try to build a VM with this and test it, please do. (I
didn't!)

There are a few more changes in the change-set. The change in rgbMul is
to remove several repeated #bitAnd: . The rest of the changes were
needed either to be able to generate the C code, or to run the simulator.

So, there are several issues that need more discussion here. Everybody,
please check the code and comment on it.

Cheers,
Juan Vuletich

'From Squeak3.10.2 of ''5 June 2008'' [latest update: #7179] on 23 October 2009 at 11:08:24 am'!

!BitBltSimulation methodsFor: 'combination rules' stamp: 'jmv 10/23/2009 09:35'!
partitionedAdd: word1 to: word2 nBits: nBits nPartitions: nParts
        "Add word1 to word2 as nParts partitions of nBits each.
        This is useful for packed pixels, or packed colors"
        | mask sum result maskedWord1 |
        self var: #word1 type: 'unsigned int'.
        self var: #word2 type: 'unsigned int'.
        self var: #mask type: 'unsigned int'.
        self var: #sum type: 'unsigned int'.
        self var: #result type: 'unsigned int'.
        self var: #maskedWord1 type: 'unsigned int'.
        mask := maskTable at: nBits.  "partition mask starts at the right"
        result := 0.
        1 to: nParts do:
                [:i |
                maskedWord1 := word1 bitAnd: mask.
                sum := maskedWord1 + (word2 bitAnd: mask).
                "result must not carry out of partition"
                (sum <= mask
                                and: [ sum >= maskedWord1 ])
                        ifTrue: [result := result bitOr: sum]
                        ifFalse: [result := result bitOr: mask].
                mask := mask << nBits  "slide left to next partition"].
        ^ result
! !

!BitBltSimulation methodsFor: 'combination rules' stamp: 'jmv 10/23/2009 09:58'!
partitionedMax: word1 with: word2 nBits: nBits nPartitions: nParts
        "Max word1 to word2 as nParts partitions of nBits each"
        | mask result |
        self var: #word1 type: 'unsigned int'.
        self var: #word2 type: 'unsigned int'.
        self var: #mask type: 'unsigned int'.
        self var: #result type: 'unsigned int'.
        mask := maskTable at: nBits.  "partition mask starts at the right"
        result := 0.
        1 to: nParts do:
                [:i |
                result := result bitOr: ((word2 bitAnd: mask) max: (word1 bitAnd: mask)).
                mask := mask << nBits  "slide left to next partition"].
        ^ result
! !

!BitBltSimulation methodsFor: 'combination rules' stamp: 'jmv 10/23/2009 11:03'!
partitionedMin: word1 with: word2 nBits: nBits nPartitions: nParts
        "Min word1 to word2 as nParts partitions of nBits each"
        | mask result |
        self var: #word1 type: 'unsigned int'.
        self var: #word2 type: 'unsigned int'.
        self var: #mask type: 'unsigned int'.
        self var: #result type: 'unsigned int'.
        mask := maskTable at: nBits.  "partition mask starts at the right"
        result := 0.
        1 to: nParts do:
                [:i |
                result := result bitOr: ((word2 bitAnd: mask) min: (word1 bitAnd: mask)).
                mask := mask << nBits  "slide left to next partition"].
        ^ result
! !

!BitBltSimulation methodsFor: 'combination rules' stamp: 'jmv 10/23/2009 11:02'!
partitionedMul: word1 with: word2 nBits: nBits nPartitions: nParts
        "Multiply word1 with word2 as nParts partitions of nBits each.
        This is useful for packed pixels, or packed colors.
        Bug in loop version when non-white background"

        | sMask product result dMask |
        sMask := maskTable at: nBits.  "partition mask starts at the right"
        dMask :=  sMask << nBits.
        result := (((word1 bitAnd: sMask)+1) * ((word2 bitAnd: sMask)+1) - 1
                                bitAnd: dMask) >> nBits. "optimized first step"
        nParts = 1
                ifTrue: [ ^result ].
        product := (((word1>>nBits bitAnd: sMask)+1) * ((word2>>nBits bitAnd: sMask)+1) - 1 bitAnd: dMask).
        result := result bitOr: product.
        nParts = 2
                ifTrue: [ ^result ].
        product := (((word1>>(2*nBits) bitAnd: sMask)+1) * ((word2>>(2*nBits) bitAnd: sMask)+1) - 1 bitAnd: dMask).
        result := result bitOr: product << nBits.
        nParts = 3
                ifTrue: [ ^result ].
        product := (((word1>>(3*nBits) bitAnd: sMask)+1) * ((word2>>(3*nBits) bitAnd: sMask)+1) - 1 bitAnd: dMask).
        result := result bitOr: product << (2*nBits).
        ^ result

" | sMask product result dMask |
        sMask := maskTable at: nBits.  'partition mask starts at the right'
        dMask :=  sMask << nBits.
        result := (((word1 bitAnd: sMask)+1) * ((word2 bitAnd: sMask)+1) - 1
                                bitAnd: dMask) >> nBits. 'optimized first step'
        nBits to: nBits * (nParts-1) by: nBits do: [:ofs |
                product := (((word1>>ofs bitAnd: sMask)+1) * ((word2>>ofs bitAnd: sMask)+1) - 1 bitAnd: dMask).
                result := result bitOr: (product bitAnd: dMask) << (ofs-nBits)].
        ^ result"! !

!BitBltSimulation methodsFor: 'combination rules' stamp: 'jmv 10/23/2009 09:57'!
partitionedSub: word1 from: word2 nBits: nBits nPartitions: nParts
        "Subtract word1 from word2 as nParts partitions of nBits each.
        This is useful for packed pixels, or packed colors"
        | mask result p1 p2 |
        self var: #word1 type: 'unsigned int'.
        self var: #word2 type: 'unsigned int'.
        self var: #p1 type: 'unsigned int'.
        self var: #p2 type: 'unsigned int'.
        self var: #mask type: 'unsigned int'.
        self var: #result type: 'unsigned int'.
        mask := maskTable at: nBits.  "partition mask starts at the right"
        result := 0.
        1 to: nParts do:
                [:i |
                p1 := word1 bitAnd: mask.
                p2 := word2 bitAnd: mask.
                p1 < p2  "result is really abs value of thedifference"
                        ifTrue: [result := result bitOr: p2 - p1]
                        ifFalse: [result := result bitOr: p1 - p2].
                mask := mask << nBits  "slide left to next partition"].
        ^ result
! !


!BitBltSimulator methodsFor: 'simulation' stamp: 'jmv 10/23/2009 09:45'!
oopForPointer: pointer
        "This gets implemented by Macros in C, where its types will also be checked.
        oop is the width of a machine word, and pointer is a raw address."

        ^ pointer! !


!CArrayAccessor methodsFor: 'accessing' stamp: 'jmv 10/23/2009 09:47'!
long32At: index
        | idx |
        idx := (offset + index) // 4 + 1.
        "Note: This is a special hack for BitBlt."
        (idx = (object basicSize + 1)) ifTrue:[^0].
        ^object basicAt: idx! !

!CArrayAccessor methodsFor: 'accessing' stamp: 'jmv 10/23/2009 09:47'!
long32At: index put: value
        ^object basicAt: (offset + index) // 4 + 1 put: value! !


!CCodeGenerator methodsFor: 'C code generator' stamp: 'jmv 10/23/2009 09:22'!
emitCConstantsOn: aStream
        "Store the global variable declarations on the given stream."
        | unused constList node |
        unused := constants keys asSet.
        methods do:[:meth|
                meth parseTree nodesDo:[:n|
                        n isConstant ifTrue:[unused remove: n name ifAbsent:[]]]].
        constList := constants keys reject:[:any| unused includes: any].
        aStream nextPutAll: '/*** Constants ***/';
                 cr.
        constList asSortedCollection do:[:varName|
                node := constants at: varName.
                node name isEmpty ifFalse:[
                        aStream nextPutAll: '#define '.
                        aStream nextPutAll: node name.
                        aStream space.
                        aStream nextPutAll: (self cLiteralFor: node value).
                        aStream cr
                ].
        ].
        aStream cr.! !

Reply | Threaded
Open this post in threaded view
|

Re: Integer overflow with BitBlt rule 20 and depth 32

David T. Lewis
 
On Fri, Oct 23, 2009 at 11:24:49AM -0300, Juan Vuletich wrote:

>
> Ok. This is my first try at this. I went back to my old 6809 assembly
> language book to remember by 2's complement aritmethic. The bit pattern
> of the result of addition and substraction is not altered by considering
> a number signed or unsigned. The only operations that are affected are
> multiplication and comparisons. rgbMul works ok because it will never
> use the most significant bit (the sign bit). So I added the correct
> types only on those operations that needed to do correct comparisons. I
> also added the check for overflow in rgbAdd (the only place where it is
> needed).
>
> I'm not sure if we should add the types everywhere, or it is ok to add
> them just to a few functions as I did. I'm running out of time today,
> anybody who can try to build a VM with this and test it, please do. (I
> didn't!)

It should be OK to add the type declarations only where they are actually
needed for comparison and multiply.

Just FYI it is worth noting that the default sqInt is an 64 bit long
when generating code for a 64 bit image VM, so it is generally good
practice to explicitly declare the int and unsigned types when doing
32 bit arithmetic. Unfortunately this looks like it would be a huge
amount of tedious work for the bitblt plugin, so I would not worry
about it for now (but it would be good to make some unit tests for
these problems so it will be possible to validate the fixes on a 64
bit image later).

I'll try building a VM this weekend if nobody else has gotten to it by
then. Note, I have zero expertise with bitblt (but I may still be able
to help with the debugging).

Dave

Reply | Threaded
Open this post in threaded view
|

Re: Integer overflow with BitBlt rule 20 and depth 32

Juan Vuletich-4
 
Hi Folks,

David T. Lewis wrote:

> It should be OK to add the type declarations only where they are actually
> needed for comparison and multiply.
>
> Just FYI it is worth noting that the default sqInt is an 64 bit long
> when generating code for a 64 bit image VM, so it is generally good
> practice to explicitly declare the int and unsigned types when doing
> 32 bit arithmetic. Unfortunately this looks like it would be a huge
> amount of tedious work for the bitblt plugin, so I would not worry
> about it for now (but it would be good to make some unit tests for
> these problems so it will be possible to validate the fixes on a 64
> bit image later).
>
> I'll try building a VM this weekend if nobody else has gotten to it by
> then. Note, I have zero expertise with bitblt (but I may still be able
> to help with the debugging).
>
> Dave
>  

Thanks for the offer Dave. I found a little more time last evening and
this morning. I built a new VM on Windows with the patch I sent
yesterday. The behavior is now correct, both on my scripts and on
Henrik's. Using Henrik's script to measure performance, I see a 2% loss
in rgbAdd, most likely because of the comparison I added. We could
unroll the loop and do the new comparison only for the most significant
partition (i.e. alpha). That would enhance the performance a little bit.

I will do a couple of tests to check that this correct behavior is
maintained, including in 64bit images and VMs.

What worries me a bit is the other changes I needed to do to be able to
run the Smalltalk BitBlt simulation and to do the translation. These are:
BitBltSimulator >> #oopForPointer:   "May be harmless"
CArrayAccessor >> #long32At:         "Why is this needed?"
CArrayAccessor >> #long32At:put:      "Why is this needed?"
CCodeGenerator >> #emitCConstantsOn:  "Consequence of recent changes to
Dictionary >> #keys. Most likely harmless. May be other senders aroud!
(yes, in the very same method there is another sender that would be
optimized by #asSet!"

I've not been following the development of VMMaker closely enough to
advise on them, so please everybody, check and comment on them.

Cheers,
Juan Vuletich
Reply | Threaded
Open this post in threaded view
|

Re: Integer overflow with BitBlt rule 20 and depth 32

David T. Lewis
 
On Sat, Oct 24, 2009 at 10:40:17AM -0300, Juan Vuletich wrote:
>
> What worries me a bit is the other changes I needed to do to be able to
> run the Smalltalk BitBlt simulation and to do the translation. These are:
> BitBltSimulator >> #oopForPointer:   "May be harmless"
> CArrayAccessor >> #long32At:         "Why is this needed?"
> CArrayAccessor >> #long32At:put:      "Why is this needed?"

I am just guessing here, but I think that BitBltSimulator expects to
be used with an interpreter simulator, so perhaps if you initialize it
with a simulator there will be no need to add these methods.

  sim := BitBltSimulator new setInterpreter: InterpreterSimulator new

Dave

Reply | Threaded
Open this post in threaded view
|

Re: Integer overflow with BitBlt rule 20 and depth 32

Juan Vuletich-4
 
Hi Folks,

I've just opened http://bugs.squeak.org/view.php?id=7407 , with a
description of the problem, several tests (based on Henrik's scripts)
and the fix I propose.

David T. Lewis wrote:

>  
> On Sat, Oct 24, 2009 at 10:40:17AM -0300, Juan Vuletich wrote:
>  
>> What worries me a bit is the other changes I needed to do to be able to
>> run the Smalltalk BitBlt simulation and to do the translation. These are:
>> BitBltSimulator >> #oopForPointer:   "May be harmless"
>> CArrayAccessor >> #long32At:         "Why is this needed?"
>> CArrayAccessor >> #long32At:put:      "Why is this needed?"
>>    
>
> I am just guessing here, but I think that BitBltSimulator expects to
> be used with an interpreter simulator, so perhaps if you initialize it
> with a simulator there will be no need to add these methods.
>
>   sim := BitBltSimulator new setInterpreter: InterpreterSimulator new
>
> Dave
>  

Given that BitBltSimulation calls #isIntegerObject: it looks like the
ivar interpreterProxy should hold an InterpreterProxy (as it already
does) and not an InterpreterSimulator. I did not add my patch to make
simulation work to Mantis, as I'm not sure about them.

Andreas, perhaps you (or anyone knowledgeable enough) can try making the
bitblt simulator tests included in the Mantis issues work. BTW, I moved
these tests to VMMaker, as the current version in trunk does test
nothing if VMMaker is not loaded. That's why these old tests didn't
catch the problem of BitBltSimulator not working anymore.

Cheers,
Juan Vuletich
Reply | Threaded
Open this post in threaded view
|

Re: Integer overflow with BitBlt rule 20 and depth 32

Eliot Miranda-2
 


On Mon, Oct 26, 2009 at 6:01 AM, Juan Vuletich <[hidden email]> wrote:

Hi Folks,

I've just opened http://bugs.squeak.org/view.php?id=7407 , with a description of the problem, several tests (based on Henrik's scripts) and the fix I propose.

David T. Lewis wrote:
 On Sat, Oct 24, 2009 at 10:40:17AM -0300, Juan Vuletich wrote:
 
What worries me a bit is the other changes I needed to do to be able to run the Smalltalk BitBlt simulation and to do the translation. These are:
BitBltSimulator >> #oopForPointer:   "May be harmless"
CArrayAccessor >> #long32At:         "Why is this needed?"
CArrayAccessor >> #long32At:put:      "Why is this needed?"
   

I am just guessing here, but I think that BitBltSimulator expects to
be used with an interpreter simulator, so perhaps if you initialize it
with a simulator there will be no need to add these methods.

 sim := BitBltSimulator new setInterpreter: InterpreterSimulator new

Dave
 

Given that BitBltSimulation calls #isIntegerObject: it looks like the ivar interpreterProxy should hold an InterpreterProxy (as it already does) and not an InterpreterSimulator. I did not add my patch to make simulation work to Mantis, as I'm not sure about them.

When simulating the interpreterProxy inst var should hold the InterpreterSimulator, not the proxy.
 
Andreas, perhaps you (or anyone knowledgeable enough) can try making the bitblt simulator tests included in the Mantis issues work. BTW, I moved these tests to VMMaker, as the current version in trunk does test nothing if VMMaker is not loaded. That's why these old tests didn't catch the problem of BitBltSimulator not working anymore.

Cheers,
Juan Vuletich

Reply | Threaded
Open this post in threaded view
|

Re: Integer overflow with BitBlt rule 20 and depth 32

Juan Vuletich-4
 
Eliot Miranda wrote:

>
> On Mon, Oct 26, 2009 at 6:01 AM, Juan Vuletich <[hidden email]
> <mailto:[hidden email]>> wrote:
>
>
>     Hi Folks,
>
>     I've just opened http://bugs.squeak.org/view.php?id=7407 , with a
>     description of the problem, several tests (based on Henrik's
>     scripts) and the fix I propose.
>
>     David T. Lewis wrote:
>
>          On Sat, Oct 24, 2009 at 10:40:17AM -0300, Juan Vuletich wrote:
>          
>
>             What worries me a bit is the other changes I needed to do
>             to be able to run the Smalltalk BitBlt simulation and to
>             do the translation. These are:
>             BitBltSimulator >> #oopForPointer:   "May be harmless"
>             CArrayAccessor >> #long32At:         "Why is this needed?"
>             CArrayAccessor >> #long32At:put:      "Why is this needed?"
>                
>
>
>         I am just guessing here, but I think that BitBltSimulator
>         expects to
>         be used with an interpreter simulator, so perhaps if you
>         initialize it
>         with a simulator there will be no need to add these methods.
>
>          sim := BitBltSimulator new setInterpreter:
>         InterpreterSimulator new
>
>         Dave
>          
>
>
>     Given that BitBltSimulation calls #isIntegerObject: it looks like
>     the ivar interpreterProxy should hold an InterpreterProxy (as it
>     already does) and not an InterpreterSimulator. I did not add my
>     patch to make simulation work to Mantis, as I'm not sure about them.
>
>
> When simulating the interpreterProxy inst var should hold the
> InterpreterSimulator, not the proxy.
>  

Maybe it should be an InterpreterSimulator when simulating the whole
interpreter. When calling #copyBitsSimulated, it is set to an
InterpreterProxy in #copyBitsFrom: .

Anyway, I'm asking for help on making #copyBitsSimulated work again,
like it should do when called from BitBltTest. If nobody can help with
that, I guess I'll open a Mantis issue for this problem, in the hope
that some day it gets fixed.

>     Andreas, perhaps you (or anyone knowledgeable enough) can try
>     making the bitblt simulator tests included in the Mantis issues
>     work. BTW, I moved these tests to VMMaker, as the current version
>     in trunk does test nothing if VMMaker is not loaded. That's why
>     these old tests didn't catch the problem of BitBltSimulator not
>     working anymore.
>
>     Cheers,
>     Juan Vuletich
>
>

Cheers,
Juan Vuletich
Reply | Threaded
Open this post in threaded view
|

Re: Integer overflow with BitBlt rule 20 and depth 32

Eliot Miranda-2
 
Hi Juan,

On Mon, Oct 26, 2009 at 11:07 AM, Juan Vuletich <[hidden email]> wrote:

Eliot Miranda wrote:


On Mon, Oct 26, 2009 at 6:01 AM, Juan Vuletich <[hidden email] <mailto:[hidden email]>> wrote:


   Hi Folks,

   I've just opened http://bugs.squeak.org/view.php?id=7407 , with a
   description of the problem, several tests (based on Henrik's
   scripts) and the fix I propose.

   David T. Lewis wrote:

        On Sat, Oct 24, 2009 at 10:40:17AM -0300, Juan Vuletich wrote:
       
           What worries me a bit is the other changes I needed to do
           to be able to run the Smalltalk BitBlt simulation and to
           do the translation. These are:
           BitBltSimulator >> #oopForPointer:   "May be harmless"
           CArrayAccessor >> #long32At:         "Why is this needed?"
           CArrayAccessor >> #long32At:put:      "Why is this needed?"
             

       I am just guessing here, but I think that BitBltSimulator
       expects to
       be used with an interpreter simulator, so perhaps if you
       initialize it
       with a simulator there will be no need to add these methods.

        sim := BitBltSimulator new setInterpreter:
       InterpreterSimulator new

       Dave
       

   Given that BitBltSimulation calls #isIntegerObject: it looks like
   the ivar interpreterProxy should hold an InterpreterProxy (as it
   already does) and not an InterpreterSimulator. I did not add my
   patch to make simulation work to Mantis, as I'm not sure about them.


When simulating the interpreterProxy inst var should hold the InterpreterSimulator, not the proxy.
 

Maybe it should be an InterpreterSimulator when simulating the whole interpreter. When calling #copyBitsSimulated, it is set to an InterpreterProxy in #copyBitsFrom: .

Anyway, I'm asking for help on making #copyBitsSimulated work again, like it should do when called from BitBltTest. If nobody can help with that, I guess I'll open a Mantis issue for this problem, in the hope that some day it gets fixed.

Well with my current VM I see no problems; all 10 tests are green.  What is the bug that you see?  How can I reproduce it?

tia
Eliot



   Andreas, perhaps you (or anyone knowledgeable enough) can try
   making the bitblt simulator tests included in the Mantis issues
   work. BTW, I moved these tests to VMMaker, as the current version
   in trunk does test nothing if VMMaker is not loaded. That's why
   these old tests didn't catch the problem of BitBltSimulator not
   working anymore.

   Cheers,
   Juan Vuletich



Cheers,
Juan Vuletich

Reply | Threaded
Open this post in threaded view
|

Re: Integer overflow with BitBlt rule 20 and depth 32

Juan Vuletich-4
 
Hi Eliot,

Eliot Miranda wrote:

>
> Hi Juan,
>
> On Mon, Oct 26, 2009 at 11:07 AM, Juan Vuletich <[hidden email]
> <mailto:[hidden email]>> wrote:
>
>
>     Eliot Miranda wrote:
>
>
>         On Mon, Oct 26, 2009 at 6:01 AM, Juan Vuletich
>         <[hidden email] <mailto:[hidden email]>
>         <mailto:[hidden email] <mailto:[hidden email]>>> wrote:
>
>
>            Hi Folks,
>
>            I've just opened http://bugs.squeak.org/view.php?id=7407 ,
>         with a
>            description of the problem, several tests (based on Henrik's
>            scripts) and the fix I propose.
>
>            David T. Lewis wrote:
>
>                 On Sat, Oct 24, 2009 at 10:40:17AM -0300, Juan
>         Vuletich wrote:
>                
>                    What worries me a bit is the other changes I needed
>         to do
>                    to be able to run the Smalltalk BitBlt simulation
>         and to
>                    do the translation. These are:
>                    BitBltSimulator >> #oopForPointer:   "May be harmless"
>                    CArrayAccessor >> #long32At:         "Why is this
>         needed?"
>                    CArrayAccessor >> #long32At:put:      "Why is this
>         needed?"
>                      
>
>                I am just guessing here, but I think that BitBltSimulator
>                expects to
>                be used with an interpreter simulator, so perhaps if you
>                initialize it
>                with a simulator there will be no need to add these
>         methods.
>
>                 sim := BitBltSimulator new setInterpreter:
>                InterpreterSimulator new
>
>                Dave
>                
>
>            Given that BitBltSimulation calls #isIntegerObject: it
>         looks like
>            the ivar interpreterProxy should hold an InterpreterProxy
>         (as it
>            already does) and not an InterpreterSimulator. I did not add my
>            patch to make simulation work to Mantis, as I'm not sure
>         about them.
>
>
>         When simulating the interpreterProxy inst var should hold the
>         InterpreterSimulator, not the proxy.
>          
>
>
>     Maybe it should be an InterpreterSimulator when simulating the
>     whole interpreter. When calling #copyBitsSimulated, it is set to
>     an InterpreterProxy in #copyBitsFrom: .
>
>     Anyway, I'm asking for help on making #copyBitsSimulated work
>     again, like it should do when called from BitBltTest. If nobody
>     can help with that, I guess I'll open a Mantis issue for this
>     problem, in the hope that some day it gets fixed.
>
>
> Well with my current VM I see no problems; all 10 tests are green.
>  What is the bug that you see?  How can I reproduce it?
>
> tia
> Eliot

Thank you for caring about this issue!

I apologize for not being clear. Check #testAlphaCompositingSimulated
and #testAlphaCompositing2Simulated. Both do nothing if BitBltSimulation
is not there. If you load VMMaker, both tests give errors. The VM in use
should be irrelevant, this is pure Smalltalk.

It is a very bad idea to have a test do nothing under default
conditions! (i.e. no special packages such as VMMaker loaded) That's why
I moved both to a new class, that should be part of VMMaker, and removed
that silly check for BitBltSimulation. This is included in the stuff I
attached to http://bugs.squeak.org/view.php?id=7407 .

Cheers,
Juan Vuletich
Reply | Threaded
Open this post in threaded view
|

Re: Integer overflow with BitBlt rule 20 and depth 32

Eliot Miranda-2
 


On Mon, Oct 26, 2009 at 1:04 PM, Juan Vuletich <[hidden email]> wrote:

Hi Eliot,

Eliot Miranda wrote:

Hi Juan,


On Mon, Oct 26, 2009 at 11:07 AM, Juan Vuletich <[hidden email] <mailto:[hidden email]>> wrote:


   Eliot Miranda wrote:


       On Mon, Oct 26, 2009 at 6:01 AM, Juan Vuletich
       <[hidden email] <mailto:[hidden email]>
       <mailto:[hidden email] <mailto:[hidden email]>>> wrote:


          Hi Folks,

          I've just opened http://bugs.squeak.org/view.php?id=7407 ,
       with a
          description of the problem, several tests (based on Henrik's
          scripts) and the fix I propose.

          David T. Lewis wrote:

               On Sat, Oct 24, 2009 at 10:40:17AM -0300, Juan
       Vuletich wrote:
                                What worries me a bit is the other changes I needed
       to do
                  to be able to run the Smalltalk BitBlt simulation
       and to
                  do the translation. These are:
                  BitBltSimulator >> #oopForPointer:   "May be harmless"
                  CArrayAccessor >> #long32At:         "Why is this
       needed?"
                  CArrayAccessor >> #long32At:put:      "Why is this
       needed?"
                   
              I am just guessing here, but I think that BitBltSimulator
              expects to
              be used with an interpreter simulator, so perhaps if you
              initialize it
              with a simulator there will be no need to add these
       methods.

               sim := BitBltSimulator new setInterpreter:
              InterpreterSimulator new

              Dave
             
          Given that BitBltSimulation calls #isIntegerObject: it
       looks like
          the ivar interpreterProxy should hold an InterpreterProxy
       (as it
          already does) and not an InterpreterSimulator. I did not add my
          patch to make simulation work to Mantis, as I'm not sure
       about them.


       When simulating the interpreterProxy inst var should hold the
       InterpreterSimulator, not the proxy.
       

   Maybe it should be an InterpreterSimulator when simulating the
   whole interpreter. When calling #copyBitsSimulated, it is set to
   an InterpreterProxy in #copyBitsFrom: .

   Anyway, I'm asking for help on making #copyBitsSimulated work
   again, like it should do when called from BitBltTest. If nobody
   can help with that, I guess I'll open a Mantis issue for this
   problem, in the hope that some day it gets fixed.


Well with my current VM I see no problems; all 10 tests are green.  What is the bug that you see?  How can I reproduce it?

tia
Eliot

Thank you for caring about this issue!

I apologize for not being clear. Check #testAlphaCompositingSimulated and #testAlphaCompositing2Simulated. Both do nothing if BitBltSimulation is not there. If you load VMMaker, both tests give errors. The VM in use should be irrelevant, this is pure Smalltalk.

I understand that.  I have an image containing BitBltSimulation and 5 different VMs :)  I'm developing Cog, a faster Squeak VM.  In my image with BitBltSimulation present all 10 BitBltTest tests pass.  But I have done some work on the simulator.

I am asking you to help me reproduce the bug and then I can export the fixes from my VM to fix VMMaker.  What version of VMMaker are you using?



It is a very bad idea to have a test do nothing under default conditions! (i.e. no special packages such as VMMaker loaded) That's why I moved both to a new class, that should be part of VMMaker, and removed that silly check for BitBltSimulation. This is included in the stuff I attached to http://bugs.squeak.org/view.php?id=7407 .

Cheers,
Juan Vuletich

Reply | Threaded
Open this post in threaded view
|

Re: Integer overflow with BitBlt rule 20 and depth 32

Juan Vuletich-4
 
Eliot Miranda wrote:

>  
>
> ------------------------------------------------------------------------
>
>
>
> On Mon, Oct 26, 2009 at 1:04 PM, Juan Vuletich <[hidden email]
> <mailto:[hidden email]>> wrote:
>
>
>     Hi Eliot,
>
>     Eliot Miranda wrote:
>
>
>         Hi Juan,
>
>
>         On Mon, Oct 26, 2009 at 11:07 AM, Juan Vuletich
>         <[hidden email] <mailto:[hidden email]>
>         <mailto:[hidden email] <mailto:[hidden email]>>> wrote:
>
>
>            Eliot Miranda wrote:
>
>
>                On Mon, Oct 26, 2009 at 6:01 AM, Juan Vuletich
>                <[hidden email] <mailto:[hidden email]>
>         <mailto:[hidden email] <mailto:[hidden email]>>
>                <mailto:[hidden email] <mailto:[hidden email]>
>         <mailto:[hidden email] <mailto:[hidden email]>>>> wrote:
>
>
>                   Hi Folks,
>
>                   I've just opened
>         http://bugs.squeak.org/view.php?id=7407 ,
>                with a
>                   description of the problem, several tests (based on
>         Henrik's
>                   scripts) and the fix I propose.
>
>                   David T. Lewis wrote:
>
>                        On Sat, Oct 24, 2009 at 10:40:17AM -0300, Juan
>                Vuletich wrote:
>                                         What worries me a bit is the
>         other changes I needed
>                to do
>                           to be able to run the Smalltalk BitBlt
>         simulation
>                and to
>                           do the translation. These are:
>                           BitBltSimulator >> #oopForPointer:   "May be
>         harmless"
>                           CArrayAccessor >> #long32At:         "Why is
>         this
>                needed?"
>                           CArrayAccessor >> #long32At:put:      "Why
>         is this
>                needed?"
>                            
>                       I am just guessing here, but I think that
>         BitBltSimulator
>                       expects to
>                       be used with an interpreter simulator, so
>         perhaps if you
>                       initialize it
>                       with a simulator there will be no need to add these
>                methods.
>
>                        sim := BitBltSimulator new setInterpreter:
>                       InterpreterSimulator new
>
>                       Dave
>                      
>                   Given that BitBltSimulation calls #isIntegerObject: it
>                looks like
>                   the ivar interpreterProxy should hold an
>         InterpreterProxy
>                (as it
>                   already does) and not an InterpreterSimulator. I did
>         not add my
>                   patch to make simulation work to Mantis, as I'm not sure
>                about them.
>
>
>                When simulating the interpreterProxy inst var should
>         hold the
>                InterpreterSimulator, not the proxy.
>                
>
>            Maybe it should be an InterpreterSimulator when simulating the
>            whole interpreter. When calling #copyBitsSimulated, it is
>         set to
>            an InterpreterProxy in #copyBitsFrom: .
>
>            Anyway, I'm asking for help on making #copyBitsSimulated work
>            again, like it should do when called from BitBltTest. If nobody
>            can help with that, I guess I'll open a Mantis issue for this
>            problem, in the hope that some day it gets fixed.
>
>
>         Well with my current VM I see no problems; all 10 tests are
>         green.  What is the bug that you see?  How can I reproduce it?
>
>         tia
>         Eliot
>
>
>     Thank you for caring about this issue!
>
>     I apologize for not being clear. Check
>     #testAlphaCompositingSimulated and
>     #testAlphaCompositing2Simulated. Both do nothing if
>     BitBltSimulation is not there. If you load VMMaker, both tests
>     give errors. The VM in use should be irrelevant, this is pure
>     Smalltalk.
>
>
> I understand that.  I have an image containing BitBltSimulation and 5
> different VMs :)  I'm developing Cog, a faster Squeak VM.  In my image
> with BitBltSimulation present all 10 BitBltTest tests pass.  But I
> have done some work on the simulator.
>
> I am asking you to help me reproduce the bug and then I can export the
> fixes from my VM to fix VMMaker.  What version of VMMaker are you using?
>

Ok. I see. I downloaded latest trunk from
http://ftp.squeak.org/trunk/Squeak3.10.2-Trunk-091024.zip.
Opened the image, open MC Browser. Add repository:
MCHttpRepository
    location: 'http://www.squeaksource.com/VMMaker'
    user: ''
    password: ''
Opened the repository
Loaded VMMaker-dtl.145.mcz
Proceeded on the warning about Klatt and FFI.
Run the tests. Both give errors.

Thanks,
Juan Vuletich

Ps. I can't wait for Cog!

>
>
>     It is a very bad idea to have a test do nothing under default
>     conditions! (i.e. no special packages such as VMMaker loaded)
>     That's why I moved both to a new class, that should be part of
>     VMMaker, and removed that silly check for BitBltSimulation. This
>     is included in the stuff I attached to
>     http://bugs.squeak.org/view.php?id=7407 .
>
>     Cheers,
>     Juan Vuletich
>

Reply | Threaded
Open this post in threaded view
|

Re: Integer overflow with BitBlt rule 20 and depth 32

David T. Lewis
In reply to this post by Juan Vuletich-4
 
On Sat, Oct 24, 2009 at 10:40:17AM -0300, Juan Vuletich wrote:

>
> What worries me a bit is the other changes I needed to do to be able to
> run the Smalltalk BitBlt simulation and to do the translation. These are:
> BitBltSimulator >> #oopForPointer:   "May be harmless"
> CArrayAccessor >> #long32At:         "Why is this needed?"
> CArrayAccessor >> #long32At:put:      "Why is this needed?"
> CCodeGenerator >> #emitCConstantsOn:  "Consequence of recent changes to
> Dictionary >> #keys. Most likely harmless. May be other senders aroud!
> (yes, in the very same method there is another sender that would be
> optimized by #asSet!"
>
> I've not been following the development of VMMaker closely enough to
> advise on them, so please everybody, check and comment on them.

Juan,

I think I finally figured out why the #oopForPointer: and #long32At: and
#long32At:put: are needed.

I went back to look at Squeak 3.7 and Squeak 3.8 images with VMMaker as
distributed in those images. The #testAlphaCompositingSimulated and
#testAlphaCompositing2Simulated tests both pass in those older images.

I then looked at a Squeak 3.8 with the latest VMMaker installed, and
these two tests fail. The difference is that when the original 64-bit
VM work was done in 2004, the #oopForPointer and #long32At: and
#long32At:put: calls were added, but not implemented in BitBltSimulator
and CArrayAccessor.  This was probably just an oversight, and the problem
has not been noticed until you spotted it now.

Therefore I think that your added #oopForPointer and #long32At: and
#long32At:put: methods are correct, and that they do need to be added
to VMMaker.

Dave

Reply | Threaded
Open this post in threaded view
|

Re: Integer overflow with BitBlt rule 20 and depth 32

David T. Lewis
In reply to this post by Eliot Miranda-2
 
On Mon, Oct 26, 2009 at 11:57:16AM -0700, Eliot Miranda wrote:

>
> On Mon, Oct 26, 2009 at 11:07 AM, Juan Vuletich <[hidden email]> wrote:
>
> > Anyway, I'm asking for help on making #copyBitsSimulated work again, like
> > it should do when called from BitBltTest. If nobody can help with that, I
> > guess I'll open a Mantis issue for this problem, in the hope that some day
> > it gets fixed.
>
> Well with my current VM I see no problems; all 10 tests are green.  What is
> the bug that you see?  How can I reproduce it?

Juan provided six new tests (see Mantis 7047) that document the problems.
I added these six tests to the trunk today, and also updated VMMaker on
SqueakSource with Juan's fixes for bitblt simulation (mainly some memory
access methods that had apparently been overlooked during the original
Squeak 64 bit work).

Juan's patches (VMMaker-BitBlt-AlphaFixes-jmv-M7407.cs on Mantis 7047)
do resolve the problems in the VM, and the changes all look correct to me
(but I have no experience with bitblt, so I'm just commenting on the fixes
for type declarations and arithmetic overflow).

Has anyone else had a chance to review this? If there are no issues or
concerns, I will add Juan's alpha fixes to VMMaker.

Dave

Reply | Threaded
Open this post in threaded view
|

Re: Integer overflow with BitBlt rule 20 and depth 32

Henrik Sperre Johansen
 
Not that it matters on 32bit architecture, but don't you in theory  
have to use unsigned long to ensure an integer of at least 32 bits is  
used?

Other than that I see no problems, until someone decides to add depths  
 > 32. (And then you'd have to modify the methods anyways).

Cheers,
Henry

On Oct 30, 2009, at 3:10 42AM, David T. Lewis wrote:

>
> On Mon, Oct 26, 2009 at 11:57:16AM -0700, Eliot Miranda wrote:
>>
>> On Mon, Oct 26, 2009 at 11:07 AM, Juan Vuletich  
>> <[hidden email]> wrote:
>>
>>> Anyway, I'm asking for help on making #copyBitsSimulated work  
>>> again, like
>>> it should do when called from BitBltTest. If nobody can help with  
>>> that, I
>>> guess I'll open a Mantis issue for this problem, in the hope that  
>>> some day
>>> it gets fixed.
>>
>> Well with my current VM I see no problems; all 10 tests are green.  
>> What is
>> the bug that you see?  How can I reproduce it?
>
> Juan provided six new tests (see Mantis 7047) that document the  
> problems.
> I added these six tests to the trunk today, and also updated VMMaker  
> on
> SqueakSource with Juan's fixes for bitblt simulation (mainly some  
> memory
> access methods that had apparently been overlooked during the original
> Squeak 64 bit work).
>
> Juan's patches (VMMaker-BitBlt-AlphaFixes-jmv-M7407.cs on Mantis 7047)
> do resolve the problems in the VM, and the changes all look correct  
> to me
> (but I have no experience with bitblt, so I'm just commenting on the  
> fixes
> for type declarations and arithmetic overflow).
>
> Has anyone else had a chance to review this? If there are no issues or
> concerns, I will add Juan's alpha fixes to VMMaker.
>
> Dave
>
>

Reply | Threaded
Open this post in threaded view
|

Re: Integer overflow with BitBlt rule 20 and depth 32

David T. Lewis
 
On Fri, Oct 30, 2009 at 10:09:36AM +0100, Henrik Johansen wrote:
>
> Not that it matters on 32bit architecture, but don't you in theory  
> have to use unsigned long to ensure an integer of at least 32 bits is  
> used?
>
> Other than that I see no problems, until someone decides to add depths  
> > 32. (And then you'd have to modify the methods anyways).

unsigned int is 32 bits on all current Squeak platforms, while
unsigned long may be 64 bits. Thus unsigned int produces the same
behavior on all current platforms, and Juan added an overflow check
in the one method for which overflow was is a problem.

Dave

12