On Sat, Mar 21, 2009 at 1:21 PM, David Röthlisberger <squ...@webcitas.ch>wrote:

>
> > I have a pharo0.1-10236dev09.02 but updated trougth: right button ->
> > system update -> to 10256. Nothing more installed.
>
> You should take a more recent pharo-dev or also update OB with
> 'ScriptLoader loadOB'.
> system update doesn't update OB.
>


David: I tried that and got the followin wallback. However, I put proceed
and senders seem to work ok. But I don't know If I breake another thing.



Error: text is already defined in a subclass of OBMercuryPanel
21 March 2009 4:38:52 pm

VM: unix - a SmalltalkImage
Image: Pharo0.1 [Latest update: #10256]

SecurityManager state:
Restricted: false
FileAccess: true
SocketAccess: true
Working Dir /home/mariano/squeak/imagenes
Trusted Dir /home/mariano/squeak/imagenes/secure
Untrusted Dir /home/mariano/squeak/imagenes/My Squeak

ClassBuilder(Object)>>error:
    Receiver: a ClassBuilder
    Arguments and temporary variables:
        aString:     'text is already defined in a subclass of
OBMercuryPanel'
    Receiver's instance variables:
        environ:     Smalltalk
        classMap:     nil
        instVarMap:     an IdentityDictionary()
        progress:     nil
        maxClassIndex:     nil
        currentClassIndex:     nil

[] in ClassBuilder>>validateInstvars:from:forSuper: {[:iv |  (usedNames
includes: iv)   ifTrue: [self error: iv , ' is already de...]}
    Arguments and temporary variables:
        instVarArray:     #('text')
        oldClass:     OBMercuryPanel
        newSuper:     OBTextPanel
        instVars:     #('text' 'browser')
        usedNames:     a Set('text')
        temp:     nil
        var:     nil
        iv:     'text'
        cl:     OBEnrichedMercuryPanel
        ivName:     nil

Array(SequenceableCollection)>>do:
    Receiver: #('text' 'browser')
    Arguments and temporary variables:
        aBlock:     [] in ClassBuilder>>validateInstvars:from:forSuper:
{[:iv |  (usedNames...etc...
        index:     1
        indexLimiT:     2
    Receiver's instance variables:
#('text' 'browser')

ClassBuilder>>validateInstvars:from:forSuper:
    Receiver: a ClassBuilder
    Arguments and temporary variables:
        instVarArray:     #('text')
        oldClass:     OBMercuryPanel
        newSuper:     OBTextPanel
        instVars:     #('text' 'browser')
        usedNames:     a Set('text')
        temp:     nil
        var:     nil
        iv:     'text'
        cl:     OBEnrichedMercuryPanel
        ivName:     nil
    Receiver's instance variables:
        environ:     Smalltalk
        classMap:     nil
        instVarMap:     an IdentityDictionary()
        progress:     nil
        maxClassIndex:     nil
        currentClassIndex:     nil


--- The full stack ---
ClassBuilder(Object)>>error:
[] in ClassBuilder>>validateInstvars:from:forSuper: {[:iv |  (usedNames
includes: iv)   ifTrue: [self error: iv , ' is already de...]}
Array(SequenceableCollection)>>do:
ClassBuilder>>validateInstvars:from:forSuper:
 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
[] in
ClassBuilder>>name:inEnvironment:subclassOf:type:instanceVariableNames:classVariableNames:poolDictionaries:category:unsafe:
{[unsafe   ifFalse: [(self validateSuperclass: newSuper forSubclass:
oldClass...]}
BlockContext>>ensure:
ClassBuilder>>name:inEnvironment:subclassOf:type:instanceVariableNames:classVariableNames:poolDictionaries:category:unsafe:
ClassBuilder>>name:inEnvironment:subclassOf:type:instanceVariableNames:classVariableNames:poolDictionaries:category:
MCClassDefinition>>createClass
MCClassDefinition>>load
MCClassDefinition(MCDefinition)>>loadOver:
[] in MCPackageLoader>>basicLoad {[:ea | ea   loadOver: (self obsoletionFor:
ea)]}
[] in OrderedCollection(SequenceableCollection)>>do:displayingProgress:
{[:each :i |  bar value: i.  aBlock value: each]}
OrderedCollection(SequenceableCollection)>>withIndexDo:
[] in OrderedCollection(SequenceableCollection)>>do:displayingProgress:
{[:bar | self   withIndexDo: [:each :i |     bar value: i.    aBlock value:
e...]}
[] in ProgressInitiationException>>defaultAction {[result := workBlock
value: progress]}
BlockContext>>ensure:
ProgressInitiationException>>defaultAction
UndefinedObject>>handleSignal:
MethodContext(ContextPart)>>handleSignal:
MethodContext(ContextPart)>>handleSignal:
MethodContext(ContextPart)>>handleSignal:
MethodContext(ContextPart)>>handleSignal:
ProgressInitiationException(Exception)>>signal
ProgressInitiationException>>display:at:from:to:during:
ProgressInitiationException class>>display:at:from:to:during:
ByteString(String)>>displayProgressAt:from:to:during:
OrderedCollection(SequenceableCollection)>>do:displayingProgress:
[] in MCPackageLoader>>basicLoad {[additions   do: [:ea | self tryToLoad:
ea]   displayingProgress: 'Loading.....]}
BlockContext>>on:do:
[] in MCPackageLoader>>basicLoad {[[additions   do: [:ea | self tryToLoad:
ea]   displayingProgress: 'Loading....]}
BlockContext>>ensure:
MCPackageLoader>>basicLoad
[] in MCPackageLoader>>loadWithNameLike: {[self basicLoad]}
[] in MCPackageLoader>>useChangeSetNamed:during: {[aBlock value]}
BlockContext>>ensure:
MCPackageLoader>>useChangeSetNamed:during:
MCPackageLoader>>useNewChangeSetNamedLike:during:
...etc...



>
> David
>
> > On Fri, Mar 20, 2009 at 8:07 PM, Mariano Martinez Peck
> > <marianop...@gmail.com <mailto:marianop...@gmail.com>> wrote:
> >
> >     Sorry...It was totally my fault :(   Sorry I nwas trying to run
> >     Algernon, but it doesn't work :(
> >
> >     I am algernon adict.
> >
> >     I did this:
> >
> >     Installer sm
> >     update;
> >     install: 'Algernon'.
> >     Installer wiresong
> >     project: 'ob';
> >     install: 'OB-Algernon'.
> >
> >
> >
> >
> >     On Fri, Mar 20, 2009 at 7:48 AM, David Röthlisberger
> >     <squ...@webcitas.ch> wrote:
> >
> >
> >          > I am trying to see the senders of a message. I select
> >         "startsWith:" in a
> >          > workspace -> right button -> extended search -> senders of it
> >         and I get
> >          > a wallback.
> >
> >         I cannot reproduce this.
> >         What kind of image do you use? Looks like a pharo-dev; but which
> >         version?
> >         Did you update it manually to 10256?
> >         #of:label: is defined for a long time in OBNavigate; which
> >         version of OB have you loaded?
> >
> >         David
> >
> >          > MessageNotUnderstood: OBShowSenders class>>of:label:
> >          > 20 March 2009 1:11:08 am
> >          >
> >          > VM: unix - a SmalltalkImage
> >          > Image: Pharo0.1 [Latest update: #10256]
> >          >
> >          > SecurityManager state:
> >          > Restricted: false
> >          > FileAccess: true
> >          > SocketAccess: true
> >          > Working Dir /home/mariano/squeak/imagenes
> >          > Trusted Dir /home/mariano/squeak/imagenes/secure
> >          > Untrusted Dir /home/mariano/squeak/imagenes/My Squeak
> >          >
> >          > OBShowSenders class(Object)>>doesNotUnderstand: #of:label:
> >          >     Receiver: OBShowSenders
> >          >     Arguments and temporary variables:
> >          >         aMessage:     of: an OBSelectorNode label: 'Senders of
> >          > startsWith: [4]'
> >          >         exception:     MessageNotUnderstood: OBShowSenders
> >         class>>of:label:
> >          >         resumeValue:     nil
> >          >     Receiver's instance variables:
> >          >         superclass:     OBNavigate
> >          >         methodDict:     a MethodDictionary(#browserClass->a
> >          > CompiledMethod (3617) #noChildr...etc...
> >          >         format:     136
> >          >         instanceVariables:     nil
> >          >         organization:     ('as yet unclassified' browserClass
> >          > noChildrenMessage)
> >          >
> >          >         subclasses:     nil
> >          >         name:     #OBShowSenders
> >          >         classPool:     nil
> >          >         sharedPools:     nil
> >          >         environment:     Smalltalk
> >          >         category:     #'OB-Standard-Announcements'
> >          >         traitComposition:     nil
> >          >         localSelectors:     nil
> >          >
> >          > DEVToolSet class>>browseSendersOf:name:autoSelect:
> >          >     Receiver: DEVToolSet
> >          >     Arguments and temporary variables:
> >          >         aSymbol:     #startsWith:
> >          >         labelString:     'Senders of startsWith: [4]'
> >          >         autoSelectString:     'startsWith:'
> >          >     Receiver's instance variables:
> >          >         superclass:     StandardToolSet
> >          >         methodDict:     a MethodDictionary()
> >          >         format:     2
> >          >         instanceVariables:     nil
> >          >         organization:     ('as yet unclassified')
> >          >
> >          >         subclasses:     nil
> >          >         name:     #DEVToolSet
> >          >         classPool:     nil
> >          >         sharedPools:     nil
> >          >         environment:     Smalltalk
> >          >         category:     #ImageForDevelopers
> >          >         traitComposition:     nil
> >          >         localSelectors:     nil
> >          >
> >          > ToolSet class>>browseSendersOf:name:autoSelect:
> >          >     Receiver: ToolSet
> >          >     Arguments and temporary variables:
> >          >         aSymbol:     #startsWith:
> >          >         titleString:     'Senders of startsWith: [4]'
> >          >         autoSelectString:     'startsWith:'
> >          >     Receiver's instance variables:
> >          >         superclass:     AppRegistry
> >          >         methodDict:     a MethodDictionary()
> >          >         format:     2
> >          >         instanceVariables:     nil
> >          >         organization:     ('as yet unclassified')
> >          >
> >          >         subclasses:     nil
> >          >         name:     #ToolSet
> >          >         classPool:     nil
> >          >         sharedPools:     nil
> >          >         environment:     Smalltalk
> >          >         category:     #'System-Applications'
> >          >         traitComposition:     nil
> >          >         localSelectors:     nil
> >          >         registeredClasses:     an
> >         OrderedCollection(StandardToolSet
> >          > OTToolset DEVToolSet)
> >          >         default:     DEVToolSet
> >          >
> >          > SystemNavigation>>browseSendersOf:name:autoSelect:
> >          >     Receiver: a SystemNavigation
> >          >     Arguments and temporary variables:
> >          >         aSelector:     #startsWith:
> >          >         labelString:     'Senders of startsWith:'
> >          >         autoSelectString:     'startsWith:'
> >          >         title:     'Senders of startsWith: [4]'
> >          >         size:     4
> >          >         senders:     an OrderedCollection(a MethodReference
> >         Algernon >>
> >          > #isMatchingClass:gi...etc...
> >          >     Receiver's instance variables:
> >          >         browserClass:     nil
> >          >         hierarchyBrowserClass:     nil
> >          >
> >          >
> >          > --- The full stack ---
> >          > OBShowSenders class(Object)>>doesNotUnderstand: #of:label:
> >          > DEVToolSet class>>browseSendersOf:name:autoSelect:
> >          > ToolSet class>>browseSendersOf:name:autoSelect:
> >          > SystemNavigation>>browseSendersOf:name:autoSelect:
> >          >  - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
> >         - - -
> >          > SystemNavigation>>browseAllCallsOn:
> >          > [] in TextMorphForShoutEditor(ParagraphEditor)>>sendersOfIt
> >         {[self
> >          > systemNavigation browseAllCallsOn: aSelector]}
> >          >
> >
> TextMorphForShoutEditor(Controller)>>terminateAndInitializeAround:
> >          > TextMorphForShoutEditor(ParagraphEditor)>>sendersOfIt
> >          > [] in PluggableShoutMorph(PluggableTextMorph)>>sendersOfIt
> >         {[textMorph
> >          > editor sendersOfIt]}
> >          > [] in PluggableShoutMorph(PluggableTextMorph)>>handleEdit:
> >         {[result :=
> >          > editBlock value]}
> >          > TextMorphForShout(TextMorph)>>handleEdit:
> >          > PluggableShoutMorph(PluggableTextMorph)>>handleEdit:
> >          > PluggableShoutMorph(PluggableTextMorph)>>sendersOfIt
> >          > UndefinedObject(Object)>>perform:orSendTo:
> >          > [] in ToggleMenuItemMorph(MenuItemMorph)>>invokeWithEvent:
> >          > {[(selArgCount := selector numArgs) = 0   ifTrue: [target
> >         perform:
> >          > selector] ...]}
> >          > BlockContext>>ensure:
> >          > CursorWithMask(Cursor)>>showWhile:
> >          > ToggleMenuItemMorph(MenuItemMorph)>>invokeWithEvent:
> >          > ToggleMenuItemMorph(MenuItemMorph)>>mouseUp:
> >          > ToggleMenuItemMorph(MenuItemMorph)>>handleMouseUp:
> >          > MouseButtonEvent>>sentTo:
> >          > ToggleMenuItemMorph(Morph)>>handleEvent:
> >          > MorphicEventDispatcher>>dispatchDefault:with:
> >          > MorphicEventDispatcher>>dispatchEvent:with:
> >          > ToggleMenuItemMorph(Morph)>>processEvent:using:
> >          > MorphicEventDispatcher>>dispatchDefault:with:
> >          > MorphicEventDispatcher>>dispatchEvent:with:
> >          > ...etc...
> >          >
> >          >
> >          >
> >
> ------------------------------------------------------------------------
> >          >
> >          > _______________________________________________
> >          > Pharo-project mailing list
> >          > Pharo-project@lists.gforge.inria.fr
> >         <mailto: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
> >         <mailto: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
>
>
> _______________________________________________
> 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