Debugger bug fix 1

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

Debugger bug fix 1

Michael Roberts-2
So I found the bug with the first assignment. It is caused by a difference between squeak and Pharo in SortedCollection. (on my phone so will be brief)

In Pharo the debugger map collection gets sorted and asked for an index for a given pc. It is supposed to answer 1 because there is no match and it is expected to be the first index for insertion. However when the asSortedCollection gets done the internal start index of the collection is 2. This manifests the bug. 2 is answered as the insertion position but this is a value internal to the collection.

Squeak does not have this bug because it forces a reset of the start index to 1. Hope that makes sense. I don't know what the correct fix is. We copy the reset:1 type code to force the collection to have start from 1 property. We check semantics of index for insertion. Is it the position of the element of index relative to pointers? Or we change the debugger to calculate the offset (but this feels wrong)

So this is an opportunity for some test cases and fixes around sorted collection if we know what the correct semantics are. This leak of '2' out of the collection is only wrong if 2 is a valid state. If that makes sense...

Cheers
Mike
Reply | Threaded
Open this post in threaded view
|

Re: Debugger bug fix 1

Stéphane Ducasse
tx mike

Stef
On Sep 8, 2011, at 2:37 PM, Michael Roberts wrote:

> So I found the bug with the first assignment. It is caused by a difference between squeak and Pharo in SortedCollection. (on my phone so will be brief)
>
> In Pharo the debugger map collection gets sorted and asked for an index for a given pc. It is supposed to answer 1 because there is no match and it is expected to be the first index for insertion. However when the asSortedCollection gets done the internal start index of the collection is 2. This manifests the bug. 2 is answered as the insertion position but this is a value internal to the collection.
>
> Squeak does not have this bug because it forces a reset of the start index to 1. Hope that makes sense. I don't know what the correct fix is. We copy the reset:1 type code to force the collection to have start from 1 property. We check semantics of index for insertion. Is it the position of the element of index relative to pointers? Or we change the debugger to calculate the offset (but this feels wrong)
>
> So this is an opportunity for some test cases and fixes around sorted collection if we know what the correct semantics are. This leak of '2' out of the collection is only wrong if 2 is a valid state. If that makes sense...
>
> Cheers
> Mike


Reply | Threaded
Open this post in threaded view
|

Re: Debugger bug fix 1

Henrik Sperre Johansen
In reply to this post by Michael Roberts-2
On 08.09.2011 14:37, Michael Roberts wrote:

> So I found the bug with the first assignment. It is caused by a difference between squeak and Pharo in SortedCollection. (on my phone so will be brief)
>
> In Pharo the debugger map collection gets sorted and asked for an index for a given pc. It is supposed to answer 1 because there is no match and it is expected to be the first index for insertion. However when the asSortedCollection gets done the internal start index of the collection is 2. This manifests the bug. 2 is answered as the insertion position but this is a value internal to the collection.
>
> Squeak does not have this bug because it forces a reset of the start index to 1. Hope that makes sense. I don't know what the correct fix is. We copy the reset:1 type code to force the collection to have start from 1 property. We check semantics of index for insertion. Is it the position of the element of index relative to pointers? Or we change the debugger to calculate the offset (but this feels wrong)
>
> So this is an opportunity for some test cases and fixes around sorted collection if we know what the correct semantics are. This leak of '2' out of the collection is only wrong if 2 is a valid state. If that makes sense...
>
> Cheers
> Mike
Hum, indexForInserting: is _supposed_ to answer the internal index...
Depending on the startIndex being 1 for doing the correct at: later is
just wrong.
Squeak potentially has the same highlight bug for different methds, as
insert:before: used when converting to SortedCollection in no way
ensures startIndex remains 1 just because it started as it.

I assume it was written this way for performance reasons, now that we
have #findBinary: aBlock, we can rewrite the code achieving same
performance using an ordinary collection, something like:

"Maintain a sorted array of intervals"
sortedSourceMap ifNil: [sortedSourceMap := self abstractSourceMap values
sorted].

"Look up which interval contains pc using a binary search"
sortedSourceMap findBinary: [: one  |
         (one includes: pc)
             ifTrue: [0]
             ifFalse: [one first > pc ifTrue: [-1] ifFalse: [1]] ]

(with some extra code needed to deal with the cases where pc < first
interval or > last interval)

Cheers,
Henry

Reply | Threaded
Open this post in threaded view
|

Re: Debugger bug fix 1

Eliot Miranda-2
Hi Henrik, Mike,

On Thu, Sep 8, 2011 at 8:02 AM, Henrik Sperre Johansen <[hidden email]> wrote:
On 08.09.2011 14:37, Michael Roberts wrote:
So I found the bug with the first assignment. It is caused by a difference between squeak and Pharo in SortedCollection. (on my phone so will be brief)

In Pharo the debugger map collection gets sorted and asked for an index for a given pc. It is supposed to answer 1 because there is no match and it is expected to be the first index for insertion. However when the asSortedCollection gets done the internal start index of the collection is 2. This manifests the bug. 2 is answered as the insertion position but this is a value internal to the collection.

Squeak does not have this bug because it forces a reset of the start index to 1. Hope that makes sense. I don't know what the correct fix is. We copy the reset:1 type code to force the collection to have start from 1 property. We check semantics of index for insertion. Is it the position of the element of index relative to pointers? Or we change the debugger to calculate the offset (but this feels wrong)

So this is an opportunity for some test cases and fixes around sorted collection if we know what the correct semantics are. This leak of '2' out of the collection is only wrong if 2 is a valid state. If that makes sense...

Cheers
Mike

Mike, thanks for your careful search!
 
Hum, indexForInserting: is _supposed_ to answer the internal index...
Depending on the startIndex being 1 for doing the correct at: later is just wrong.
Squeak potentially has the same highlight bug for different methds, as insert:before: used when converting to SortedCollection in no way ensures startIndex remains 1 just because it started as it.

This is an ancient bug.  I copied the code from Debugger and it's been there since at least Smalltalk-80 V2:

!Debugger methodsFor: 'pc selection'!
pcRange
    "Answer the indices in the source code for the method corresponding
    to the selected context's program counter value."

    | i methodNode pc end |
    (HighlightPC and: [context ~~ nil])
        ifFalse: [^1 to: 0].
    (sourceMap == nil or: [sourceMap size = 0])
         ifTrue: [^1 to: 0].
    pc_ context pc -
        ((context == processHandle topContext and: [processHandle interrupted])
            ifTrue: [1]
            ifFalse: [2]).
    i _ sourceMap indexForInserting: (Association key: pc value: nil).
    i < 1 ifTrue: [^1 to: 0].
    i > sourceMap size
        ifTrue:
            [end _ sourceMap inject: 0 into:
                [:prev :this | prev max: this value last].
            ^ end+1 to: end].
    ^(sourceMap at: i) value! !

In Smalltalk-80 V2 indexForInserting: is also private, but like Squeak it "just works" since firstIndex is 1 in this context.  So either take your approach or add a non-private accessor to SortedCollection than answers an external index. Personally I like the external accessor, since findBinary: doesn't quite do what we want.  In my Qwaq-derived image Josh Gargus contributed findNearbyBinaryIndex: which is nearly what we want:


!SequenceableCollection methodsFor: 'enumerating' stamp: 'jcg 1/27/2009 18:32'!
findNearbyBinaryIndex: aBlock
"Search for an element in the receiver using binary search.
The argument aBlock is a one-element block returning
0 - if the element is the one searched for
<0 - if the search should continue in the first half
>0 - if the search should continue in the second half
If no matching element is found, answer the closest index we could find."
| index low high test |
low := 1.
high := self size.
[index := high + low // 2.
low > high] whileFalse:[
test := aBlock value: (self at: index).
test = 0 
ifTrue:[^index]
ifFalse:[test > 0
ifTrue: [low := index + 1]
ifFalse: [high := index - 1]]].
^index! !

but it doesn't answer an index > size when the searched for element should be past the end. 

#(1 3 5 7 11 15 23) findNearbyBinaryIndex: [ :arg | 0 - arg ] 0

#(1 3 5 7 11 15 23) findNearbyBinaryIndex: [ :arg | 24 - arg ] 7

I think it should read
!SequenceableCollection methodsFor: 'enumerating' stamp: 'eem 9/8/2011 10:23'!
findNearbyBinaryIndex: aBlock
"Search for an element in the receiver using binary search.
The argument aBlock is a one-element block returning
0 - if the element is the one searched for
<0 - if the search should continue in the first half
>0 - if the search should continue in the second half
If no matching element is found, answer the closest index we could find."
| index low high test |
low := 1.
high := self size.
[index := high + low // 2.
low > high] whileFalse:[
test := aBlock value: (self at: index).
test = 0 
ifTrue:[^index]
ifFalse:[test > 0
ifTrue: [low := index + 1]
ifFalse: [high := index - 1]]].
^index = self size ifTrue: [index + 1] ifFalse: [index]! !

and then

#(1 3 5 7 11 15 23) findNearbyBinaryIndex: [ :arg | 0 - arg ] 0

#(1 3 5 7 11 15 23) findNearbyBinaryIndex: [ :arg | 24 - arg ] 8

and then the debugger method uses simply

i := sortedSourceMap findNearbyBinaryIndex: [:assoc| pc - assoc key].

in place of

i := sortedSourceMap indexForInserting: (pc -> nil)].

Find attached.  I'll add this to Squeak trunk.


I assume it was written this way for performance reasons, now that we have #findBinary: aBlock, we can rewrite the code achieving same performance using an ordinary collection, something like:

"Maintain a sorted array of intervals"
sortedSourceMap ifNil: [sortedSourceMap := self abstractSourceMap values sorted].

"Look up which interval contains pc using a binary search"
sortedSourceMap findBinary: [: one  |
       (one includes: pc)
           ifTrue: [0]
           ifFalse: [one first > pc ifTrue: [-1] ifFalse: [1]] ]

(with some extra code needed to deal with the cases where pc < first interval or > last interval)

Cheers,
Henry




--
best,
Eliot


SequenceableCollection-findNearbyBinaryIndex.st (2K) Download Attachment
DebuggerMethodMap-rangeForPCcontextIsActiveContext.st (2K) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: Debugger bug fix 1

Eliot Miranda-2
Hmmm, let me correct the comment in findNearbyBinaryIndex:.  Find attached.

On Thu, Sep 8, 2011 at 10:34 AM, Eliot Miranda <[hidden email]> wrote:
Hi Henrik, Mike,

On Thu, Sep 8, 2011 at 8:02 AM, Henrik Sperre Johansen <[hidden email]> wrote:
On 08.09.2011 14:37, Michael Roberts wrote:
So I found the bug with the first assignment. It is caused by a difference between squeak and Pharo in SortedCollection. (on my phone so will be brief)

In Pharo the debugger map collection gets sorted and asked for an index for a given pc. It is supposed to answer 1 because there is no match and it is expected to be the first index for insertion. However when the asSortedCollection gets done the internal start index of the collection is 2. This manifests the bug. 2 is answered as the insertion position but this is a value internal to the collection.

Squeak does not have this bug because it forces a reset of the start index to 1. Hope that makes sense. I don't know what the correct fix is. We copy the reset:1 type code to force the collection to have start from 1 property. We check semantics of index for insertion. Is it the position of the element of index relative to pointers? Or we change the debugger to calculate the offset (but this feels wrong)

So this is an opportunity for some test cases and fixes around sorted collection if we know what the correct semantics are. This leak of '2' out of the collection is only wrong if 2 is a valid state. If that makes sense...

Cheers
Mike

Mike, thanks for your careful search!
 
Hum, indexForInserting: is _supposed_ to answer the internal index...
Depending on the startIndex being 1 for doing the correct at: later is just wrong.
Squeak potentially has the same highlight bug for different methds, as insert:before: used when converting to SortedCollection in no way ensures startIndex remains 1 just because it started as it.

This is an ancient bug.  I copied the code from Debugger and it's been there since at least Smalltalk-80 V2:

!Debugger methodsFor: 'pc selection'!
pcRange
    "Answer the indices in the source code for the method corresponding
    to the selected context's program counter value."

    | i methodNode pc end |
    (HighlightPC and: [context ~~ nil])
        ifFalse: [^1 to: 0].
    (sourceMap == nil or: [sourceMap size = 0])
         ifTrue: [^1 to: 0].
    pc_ context pc -
        ((context == processHandle topContext and: [processHandle interrupted])
            ifTrue: [1]
            ifFalse: [2]).
    i _ sourceMap indexForInserting: (Association key: pc value: nil).
    i < 1 ifTrue: [^1 to: 0].
    i > sourceMap size
        ifTrue:
            [end _ sourceMap inject: 0 into:
                [:prev :this | prev max: this value last].
            ^ end+1 to: end].
    ^(sourceMap at: i) value! !

In Smalltalk-80 V2 indexForInserting: is also private, but like Squeak it "just works" since firstIndex is 1 in this context.  So either take your approach or add a non-private accessor to SortedCollection than answers an external index. Personally I like the external accessor, since findBinary: doesn't quite do what we want.  In my Qwaq-derived image Josh Gargus contributed findNearbyBinaryIndex: which is nearly what we want:


!SequenceableCollection methodsFor: 'enumerating' stamp: 'jcg 1/27/2009 18:32'!
findNearbyBinaryIndex: aBlock
"Search for an element in the receiver using binary search.
The argument aBlock is a one-element block returning
0 - if the element is the one searched for
<0 - if the search should continue in the first half
>0 - if the search should continue in the second half
If no matching element is found, answer the closest index we could find."
| index low high test |
low := 1.
high := self size.
[index := high + low // 2.
low > high] whileFalse:[
test := aBlock value: (self at: index).
test = 0 
ifTrue:[^index]
ifFalse:[test > 0
ifTrue: [low := index + 1]
ifFalse: [high := index - 1]]].
^index! !

but it doesn't answer an index > size when the searched for element should be past the end. 

#(1 3 5 7 11 15 23) findNearbyBinaryIndex: [ :arg | 0 - arg ] 0

#(1 3 5 7 11 15 23) findNearbyBinaryIndex: [ :arg | 24 - arg ] 7

I think it should read
!SequenceableCollection methodsFor: 'enumerating' stamp: 'eem 9/8/2011 10:23'!
findNearbyBinaryIndex: aBlock
"Search for an element in the receiver using binary search.
The argument aBlock is a one-element block returning
0 - if the element is the one searched for
<0 - if the search should continue in the first half
>0 - if the search should continue in the second half
If no matching element is found, answer the closest index we could find."
| index low high test |
low := 1.
high := self size.
[index := high + low // 2.
low > high] whileFalse:[
test := aBlock value: (self at: index).
test = 0 
ifTrue:[^index]
ifFalse:[test > 0
ifTrue: [low := index + 1]
ifFalse: [high := index - 1]]].
^index = self size ifTrue: [index + 1] ifFalse: [index]! !

and then

#(1 3 5 7 11 15 23) findNearbyBinaryIndex: [ :arg | 0 - arg ] 0

#(1 3 5 7 11 15 23) findNearbyBinaryIndex: [ :arg | 24 - arg ] 8

and then the debugger method uses simply

i := sortedSourceMap findNearbyBinaryIndex: [:assoc| pc - assoc key].

in place of

i := sortedSourceMap indexForInserting: (pc -> nil)].

Find attached.  I'll add this to Squeak trunk.


I assume it was written this way for performance reasons, now that we have #findBinary: aBlock, we can rewrite the code achieving same performance using an ordinary collection, something like:

"Maintain a sorted array of intervals"
sortedSourceMap ifNil: [sortedSourceMap := self abstractSourceMap values sorted].

"Look up which interval contains pc using a binary search"
sortedSourceMap findBinary: [: one  |
       (one includes: pc)
           ifTrue: [0]
           ifFalse: [one first > pc ifTrue: [-1] ifFalse: [1]] ]

(with some extra code needed to deal with the cases where pc < first interval or > last interval)

Cheers,
Henry




--
best,
Eliot




--
best,
Eliot


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

Re: Debugger bug fix 1

Henrik Sperre Johansen
On 08.09.2011 19:39, Eliot Miranda wrote:
Hmmm, let me correct the comment in findNearbyBinaryIndex:.  Find attached.

On Thu, Sep 8, 2011 at 10:34 AM, Eliot Miranda <[hidden email]> wrote:
Hi Henrik, Mike,

On Thu, Sep 8, 2011 at 8:02 AM, Henrik Sperre Johansen <[hidden email]> wrote:
On 08.09.2011 14:37, Michael Roberts wrote:
So I found the bug with the first assignment. It is caused by a difference between squeak and Pharo in SortedCollection. (on my phone so will be brief)

In Pharo the debugger map collection gets sorted and asked for an index for a given pc. It is supposed to answer 1 because there is no match and it is expected to be the first index for insertion. However when the asSortedCollection gets done the internal start index of the collection is 2. This manifests the bug. 2 is answered as the insertion position but this is a value internal to the collection.

Squeak does not have this bug because it forces a reset of the start index to 1. Hope that makes sense. I don't know what the correct fix is. We copy the reset:1 type code to force the collection to have start from 1 property. We check semantics of index for insertion. Is it the position of the element of index relative to pointers? Or we change the debugger to calculate the offset (but this feels wrong)

So this is an opportunity for some test cases and fixes around sorted collection if we know what the correct semantics are. This leak of '2' out of the collection is only wrong if 2 is a valid state. If that makes sense...

Cheers
Mike

Mike, thanks for your careful search!
 
Hum, indexForInserting: is _supposed_ to answer the internal index...
Depending on the startIndex being 1 for doing the correct at: later is just wrong.
Squeak potentially has the same highlight bug for different methds, as insert:before: used when converting to SortedCollection in no way ensures startIndex remains 1 just because it started as it.

This is an ancient bug.  I copied the code from Debugger and it's been there since at least Smalltalk-80 V2:

!Debugger methodsFor: 'pc selection'!
pcRange
    "Answer the indices in the source code for the method corresponding
    to the selected context's program counter value."

    | i methodNode pc end |
    (HighlightPC and: [context ~~ nil])
        ifFalse: [^1 to: 0].
    (sourceMap == nil or: [sourceMap size = 0])
         ifTrue: [^1 to: 0].
    pc_ context pc -
        ((context == processHandle topContext and: [processHandle interrupted])
            ifTrue: [1]
            ifFalse: [2]).
    i _ sourceMap indexForInserting: (Association key: pc value: nil).
    i < 1 ifTrue: [^1 to: 0].
    i > sourceMap size
        ifTrue:
            [end _ sourceMap inject: 0 into:
                [:prev :this | prev max: this value last].
            ^ end+1 to: end].
    ^(sourceMap at: i) value! !

In Smalltalk-80 V2 indexForInserting: is also private, but like Squeak it "just works" since firstIndex is 1 in this context.  So either take your approach or add a non-private accessor to SortedCollection than answers an external index. Personally I like the external accessor, since findBinary: doesn't quite do what we want.  In my Qwaq-derived image Josh Gargus contributed findNearbyBinaryIndex: which is nearly what we want:


!SequenceableCollection methodsFor: 'enumerating' stamp: 'jcg 1/27/2009 18:32'!
findNearbyBinaryIndex: aBlock
"Search for an element in the receiver using binary search.
The argument aBlock is a one-element block returning
0 - if the element is the one searched for
<0 - if the search should continue in the first half
>0 - if the search should continue in the second half
If no matching element is found, answer the closest index we could find."
| index low high test |
low := 1.
high := self size.
[index := high + low // 2.
low > high] whileFalse:[
test := aBlock value: (self at: index).
test = 0 
ifTrue:[^index]
ifFalse:[test > 0
ifTrue: [low := index + 1]
ifFalse: [high := index - 1]]].
^index! !

but it doesn't answer an index > size when the searched for element should be past the end. 

#(1 3 5 7 11 15 23) findNearbyBinaryIndex: [ :arg | 0 - arg ] 0

#(1 3 5 7 11 15 23) findNearbyBinaryIndex: [ :arg | 24 - arg ] 7

I think it should read
!SequenceableCollection methodsFor: 'enumerating' stamp: 'eem 9/8/2011 10:23'!
findNearbyBinaryIndex: aBlock
"Search for an element in the receiver using binary search.
The argument aBlock is a one-element block returning
0 - if the element is the one searched for
<0 - if the search should continue in the first half
>0 - if the search should continue in the second half
If no matching element is found, answer the closest index we could find."
| index low high test |
low := 1.
high := self size.
[index := high + low // 2.
low > high] whileFalse:[
test := aBlock value: (self at: index).
test = 0 
ifTrue:[^index]
ifFalse:[test > 0
ifTrue: [low := index + 1]
ifFalse: [high := index - 1]]].
^index = self size ifTrue: [index + 1] ifFalse: [index]! !

and then

#(1 3 5 7 11 15 23) findNearbyBinaryIndex: [ :arg | 0 - arg ] 0

#(1 3 5 7 11 15 23) findNearbyBinaryIndex: [ :arg | 24 - arg ] 8

and then the debugger method uses simply

i := sortedSourceMap findNearbyBinaryIndex: [:assoc| pc - assoc key].

in place of

i := sortedSourceMap indexForInserting: (pc -> nil)].

Find attached.  I'll add this to Squeak trunk.

That certainly works!
While we're at it though, why not try to improve the code abit as well?

A couple of suggestions:

- Readability of first part could benefit from refactoring into a separate method:
DebuggerMethodMap>> #abstractPCFor: aConcretePC when: contextIsActiveContext
"If the context is the actve context (is at the hot end of the stack)
  then its pc is the current pc.  But if the context isn't, because it is
  suspended sending a message, then its current pc is the previous pc"
^self method abstractPCForConcretePC:
    (contextIsActiveContext ifTrue: [contextsConcretePC]
                                                ifFalse: [(self method pcPreviousTo: contextsConcretePC) ifNil: [contextsConcretePC]].

- The range interval will be invalid whether it's up front or behind, does it really matter if it's invalid from 1 to 0 or from end +1 to end?
If it's only used for highlighting, neither will result in anything actually being highlighted.
Then, we could still use findBinary, I like your pc - assoc key better:
^self abstractSourceMap at: pc ifAbsent:
    [(self sortedSourceMap findBinary: [:assoc | pc - assoc key ] ifAbsent: [nil -> (1 to: 0)]) value]


- And of course:
>> #sortedSourceMap
^sortedSourceMap ifNil: [sortedSourceMap := self abstractSourceMap associations sorted]

- So we end up with:
DebuggerMethodMap>>rangeForPC:contextIsActiveContext: (in category 'source mapping') -----
  rangeForPC: concretePC contextIsActiveContext: contextIsActive
  "Answer the indices in the source code for the supplied pc."
| pc |
pc := self abstractPCFor: concretePC when: contextIsActive.
^self abstractSourceMap at: pc ifAbsent:
    [(self sortedSourceMap findBinary: [:assoc | pc - assoc key ] ifAbsent: [nil -> (1 to: 0)]) value]

Which (at least to me) is quite a bit easier to read... Nested ifAbsent: calls still ain't very pretty, but hey.

Cheers,
Henry


Reply | Threaded
Open this post in threaded view
|

Re: Debugger bug fix 1

Stéphane Ducasse
In reply to this post by Michael Roberts-2
Hi guys

I'm a bit busy (too much to follow carefully).
Just tell me what I should integrate and I will do it fast.

Stef

On Sep 8, 2011, at 2:37 PM, Michael Roberts wrote:

> So I found the bug with the first assignment. It is caused by a difference between squeak and Pharo in SortedCollection. (on my phone so will be brief)
>
> In Pharo the debugger map collection gets sorted and asked for an index for a given pc. It is supposed to answer 1 because there is no match and it is expected to be the first index for insertion. However when the asSortedCollection gets done the internal start index of the collection is 2. This manifests the bug. 2 is answered as the insertion position but this is a value internal to the collection.
>
> Squeak does not have this bug because it forces a reset of the start index to 1. Hope that makes sense. I don't know what the correct fix is. We copy the reset:1 type code to force the collection to have start from 1 property. We check semantics of index for insertion. Is it the position of the element of index relative to pointers? Or we change the debugger to calculate the offset (but this feels wrong)
>
> So this is an opportunity for some test cases and fixes around sorted collection if we know what the correct semantics are. This leak of '2' out of the collection is only wrong if 2 is a valid state. If that makes sense...
>
> Cheers
> Mike


Reply | Threaded
Open this post in threaded view
|

Re: Debugger bug fix 1

Michael Roberts-2
sorry guys, i have not had time to be online much. Eliot, guys, thanks
for the code (Phillipe, Hi!). I think i saw marcus comment on the
tracker that something sensible had been done?

i just wanted to offer a thought that we do not change the original
Pharo debugger too much from Squeak. i saw a recent issue # that was a
'debugger refactoring'. tracking merges & bugs between Squeak and
Pharo is hard, it would be nice to concentrate on pure fixes where
possible.... (if you itch to refactor...help Doru with the new
debugger model etc).

cheers
Mike

On Thu, Sep 8, 2011 at 9:37 PM, Stéphane Ducasse
<[hidden email]> wrote:

> Hi guys
>
> I'm a bit busy (too much to follow carefully).
> Just tell me what I should integrate and I will do it fast.
>
> Stef
>
> On Sep 8, 2011, at 2:37 PM, Michael Roberts wrote:
>
>> So I found the bug with the first assignment. It is caused by a difference between squeak and Pharo in SortedCollection. (on my phone so will be brief)
>>
>> In Pharo the debugger map collection gets sorted and asked for an index for a given pc. It is supposed to answer 1 because there is no match and it is expected to be the first index for insertion. However when the asSortedCollection gets done the internal start index of the collection is 2. This manifests the bug. 2 is answered as the insertion position but this is a value internal to the collection.
>>
>> Squeak does not have this bug because it forces a reset of the start index to 1. Hope that makes sense. I don't know what the correct fix is. We copy the reset:1 type code to force the collection to have start from 1 property. We check semantics of index for insertion. Is it the position of the element of index relative to pointers? Or we change the debugger to calculate the offset (but this feels wrong)
>>
>> So this is an opportunity for some test cases and fixes around sorted collection if we know what the correct semantics are. This leak of '2' out of the collection is only wrong if 2 is a valid state. If that makes sense...
>>
>> Cheers
>> Mike
>
>
>