Thanks.

I think that for the MouseOverHandler it would be good to know if this  
is related to Sensor changes.
Mike what you think?

Stef

On Jun 3, 2009, at 11:38 PM, Hernan Wilkinson wrote:

> Hi,
>  I know this is not the right way to send fixes, but it is the  
> fastest... so maybe it is useful for those who need them.
>  I had a lot of problems using the last pharo image, some are  
> related with the new debugger, some are old errors related with  
> buttons, some are related with the OmmiBrowser (I send them here too  
> because I know that the OB authors are subscribed to this list and  
> because that is the main pharo browser), etc.
>  Most of the problems are because nil receives a message that does  
> not understand. I did not look for the reason that made the variable  
> reference nil (maybe the best solution) but only added a #isNil  
> check (the fastest solution).
>  I had to disable the new debugger and get back to the old one  
> (Debugger) because I was getting to many errors with the new one  
> saying "It could not debug a running process".
>  Here are the fixes:
>
> 1) This one made the image to crash because it entered a infinite  
> loop. The problem is that sometime getStateSelector is nil.
>
> PluggableButtonMorph>>getModelState
>       "Answer the result of sending the receiver's model the  
> getStateSelector message."
>
>       ^(getStateSelector isNil or: [ model isNil ])
>               ifTrue: [false]
>               ifFalse: [model perform: getStateSelector]
> ---------------
>
> 2) This one is related with what Sean Allen reported. Again  
> leftMorphs is nil, so I added a #isNil check. (For me this class is  
> a mess, but I do not have the experience to change it yet)
>
> MouseOverHandler>>noticeMouseOver: aMorph event: anEvent
>       "Remember that the mouse is currently over some morph"
>       leftMorphs isNil ifFalse: [
>               (leftMorphs includes: aMorph)
>                       ifTrue:[leftMorphs remove: aMorph]
>                       ifFalse:[enteredMorphs nextPut: aMorph].
>               overMorphs nextPut: aMorph.]
> --------------
>
> 3) OCompletion does not work with the old debugger  
> because#guessTypeForName: references tempNames that is not  
> defined... So I just disallowed it.
>
> Debugger>>guessTypeForName: aString
>       | index object |
>       index := nil. "tempNames
>                               indexOf: aString
>                               ifAbsent: []."
>       object := index
>                               ifNil: [index := self receiver class 
> allInstVarNames
>                                                               indexOf: aString
>                                                               ifAbsent: [].
>                                               index ifNil: [^ nil].
>                                       self receiver instVarAt: index]
>                               ifNotNil: [self selectedContext tempAt: index].
>       ^ object class
> --------------
> All the rest are OB related.
> 4) When pressing the mouse right button (on windows) I had a error  
> saying OBTextSelection does not understand #isClassNode, so I  
> implemented returning false. Again, I did not verify if an  
> OBTextSelection should receive that message or not, I just  
> implemented.
>
> OBTextSelection>>isClassNode
>
>       ^false
> ---------------
> 5) After loading a Monticello package I could not open an OB browser  
> anymore. Again, the problem is that ea is nil sometimes.
>
> OBBrowser>>scanNodeCommands: ann
>       (cmdFactories select: [:ea | ea notNil and: [ ea takesNodes]])
>               do: [:ea | ann addFactory: ea]
> -------------------
> 6) Similar to 5.
>
> OBBrowser>>scanTextCommands: ann
>       (cmdFactories select: [:ea | ea notNil and: [ ea takesText ]]) do:  
> [:ea | ann addFactory: ea]
> ------------------
> 7) This is an error I reported to OB a long time ago, related with  
> pressing or selecting the cancel option.
>
> OBDefinitionPanel>>aboutToChange: ann
>
>     | ans answerResult vetoBlock |
>
>     self canDiscardEdits ifTrue: [^ true].
>     vetoBlock := [ ann veto ].
>     ans := OBChoiceRequest
>             prompt: 'Code has been modified. Do you want to accept  
> or discard the changes?'
>             labels: {'Accept'. 'Discard'. 'Cancel'}
>             values: (Array
>                         with: [self changed: #accept]
>                         with: [self changed: #clearUserEdits]
>                         with: vetoBlock ).
>
>     answerResult := ans value.
>        answerResult isNil ifTrue: vetoBlock.
> --------------------
>
> I hope it helps.
>
> Hernan.
> _______________________________________________
> Pharo-project mailing list
> Pharo-project@lists.gforge.inria.fr
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


_______________________________________________
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Reply via email to