[squeak-dev] The Trunk: Tools-cmm.347.mcz

Chris Muller asqueaker at gmail.com
Mon Jan 27 03:08:57 UTC 2014


Browsing all class-vars of a class at once?  Is that something you
want to do very often?  Fewer than 5% [1] of classes in the system
have more than one class var.  Maybe it's a sign of having too many
class-vars in a class..?

If looking one of the 4.2% of classes that have more than 1 class var,
their individual values can be inspected straight from the definition,
and the class itself explored simply by double clicking the class name
pressing Command+Shift+I.  The classPool is presented right there.
That's only +2 gestures for this pretty rare(?) thing.

Of all the entries in that menu, "browse class vars" is the one that
stands alone.

So it seems like we shouldn't have it in the menu.

[1] -- (((Object withAllSubclasses count: [ : e | e classVarNames size
> 1 ]) / Object withAllSubclasses size)) asFloat

On Sun, Jan 26, 2014 at 3:07 PM, karl ramberg <karlramberg at gmail.com> wrote:
> I miss the menu options to inspect and explore class variables.
> This change makes it much harder to inspect values stored in class variables
>
> Cheers,
> Karl
>
>
>
> On Tue, May 3, 2011 at 1:36 AM, <commits at source.squeak.org> wrote:
>>
>> Chris Muller uploaded a new version of Tools to project The Trunk:
>> http://source.squeak.org/trunk/Tools-cmm.347.mcz
>>
>> ==================== Summary ====================
>>
>> Name: Tools-cmm.347
>> Author: cmm
>> Time: 2 May 2011, 6:36:40.244 pm
>> UUID: 977c180b-7c15-4200-9ceb-319d2e850364
>> Ancestors: Tools-fbs.346, Tools-fbs.345
>>
>> - Update menu "inst var defs" to "assignments..." and "inst var refs" to
>> "references...".  Each option now includes a selection of the available
>> class-variables, enabling "class var refs" to be removed.  Each option also
>> has an appropriate hot-key assignment.
>> - Removed "class vars" because one could simply explore the class'
>> classPool.
>>
>> =============== Diff against Tools-fbs.346 ===============
>>
>> Item was changed:
>>   ----- Method: Browser>>classListMenu:shifted: (in category 'class
>> functions') -----
>>   classListMenu: aMenu shifted: shifted
>>         "Set up the menu to apply to the receiver's class list, honoring
>> the #shifted boolean"
>>         self
>>                 menuHook: aMenu
>>                 named: #classListMenu
>>                 shifted: shifted.
>>         Preferences useOnlyServicesInMenu ifTrue:[^aMenu].
>>         shifted ifTrue:[^ self shiftedClassListMenu: aMenu].
>>         aMenu addList: #(
>>                 -
>>                 ('browse full (b)'                      browseMethodFull)
>>                 ('browse hierarchy (h)'         spawnHierarchy)
>>                 ('browse protocol (p)'          browseFullProtocol)
>>                 -
>>                 ('printOut'
>> printOutClass)
>>                 ('fileOut'
>> fileOutClass)
>>                 -
>>                 ('show hierarchy'                       hierarchy)
>>                 ('show definition'                      editClass)
>>                 ('show comment'                 editComment)
>>                 -
>> +               ('references... (r)'
>> browseVariableReferences)
>> +               ('assignments... (a)'
>> browseVariableAssignments)
>> -               ('inst var refs...'                     browseInstVarRefs)
>> -               ('inst var defs...'                     browseInstVarDefs)
>> -               -
>> -               ('class var refs...'
>> browseClassVarRefs)
>> -               ('class vars'
>> browseClassVariables)
>>                 ('class refs (N)'
>> browseClassRefs)
>>                 -
>>                 ('rename class ...'                     renameClass)
>>                 ('copy class'                           copyClass)
>>                 ('remove class (x)'                     removeClass)
>>                 -
>>                 ('find method...'
>> findMethod)
>>                 -
>>                 ('more...'
>> offerShiftedClassListMenu)).
>>         ^ aMenu
>>   !
>>
>> Item was changed:
>>   ----- Method: Browser>>messageListMenu:shifted: (in category 'message
>> functions') -----
>>   messageListMenu: aMenu shifted: shifted
>>         "Answer the message-list menu"
>>         self
>>                 menuHook: aMenu
>>                 named: #messageListMenu
>>                 shifted: shifted.
>>         Preferences useOnlyServicesInMenu ifTrue:[^aMenu].
>>         shifted ifTrue: [^ self shiftedMessageListMenu: aMenu].
>>         aMenu addList: #(
>>                         ('what to show...'
>> offerWhatToShowMenu)
>>                         ('toggle break on entry'
>> toggleBreakOnEntry)
>>                         -
>>                         ('browse full (b)'
>> browseMethodFull)
>>                         ('browse hierarchy (h)'
>> classHierarchy)
>>                         ('browse method (O)'
>> openSingleMessageBrowser)
>>                         ('browse protocol (p)'
>> browseFullProtocol)
>>                         -
>>                         ('fileOut'
>> fileOutMessage)
>>                         ('printOut'
>> printOutMessage)
>>                         ('copy selector (c)'
>> copySelector)
>>                         ('copy reference'
>> copyReference)
>>                         -
>>                         ('senders of... (n)'
>> browseSendersOfMessages)
>>                         ('implementors of... (m)'
>> browseMessages)
>>                         ('inheritance (i)'
>> methodHierarchy)
>>                         ('versions (v)'
>> browseVersions)
>>                         -
>> +                       ('references... (r)'
>> browseVariableReferences)
>> +                       ('assignments... (a)'
>> browseVariableAssignments)
>> -                       ('inst var refs...'
>> browseInstVarRefs)
>> -                       ('inst var defs...'
>> browseInstVarDefs)
>> -                       ('class var refs...'
>> browseClassVarRefs)
>> -                       ('class variables'
>> browseClassVariables)
>>                         ('class refs (N)'
>> browseClassRefs)
>>                         -
>>                         ('remove method (x)'
>> removeMessage)
>>                         ('explore method'
>> exploreMethod)
>>                         ('inspect method'
>> inspectMethod)
>>                         -
>>                         ('more...'
>> shiftedYellowButtonActivity)).
>>         ^ aMenu!
>>
>> Item was changed:
>>   ----- Method: Browser>>reformulateList (in category 'message list')
>> -----
>>   reformulateList
>>         "If the receiver has a way of reformulating its message list, here
>> is a chance for it to do so"
>>         super reformulateList.
>>         (self messageList includes: self selectedMessageName)
>> +               ifFalse: [ self messageList
>> +                                       ifEmpty: [ self
>> selectMessageNamed: nil ]
>> +                                       ifNotEmpty: [ self
>> selectMessageNamed: self lastMessageName ]].!
>> -               ifFalse: [ self selectMessageNamed: self lastMessageName
>> ].!
>>
>> Item was changed:
>>   ----- Method: ChangeSorter>>classListMenu:shifted: (in category 'class
>> list') -----
>>   classListMenu: aMenu shifted: shifted
>>         "Fill aMenu with items appropriate for the class list"
>>
>>         aMenu title: 'class list'.
>>         aMenu addStayUpItemSpecial.
>>         (parent notNil and: [shifted not])
>>                 ifTrue: [aMenu addList: #( "These two only apply to dual
>> change sorters"
>>                         ('copy class chgs to other side'
>> copyClassToOther)
>>                         ('move class chgs to other side'
>> moveClassToOther))].
>>
>>         aMenu addList: (shifted
>>                 ifFalse: [#(
>>                         -
>>                         ('delete class from change set (d)'
>> forgetClass)
>>                         ('remove class from system (x)'
>> removeClass)
>>                         -
>>                         ('browse full (b)'
>> browseMethodFull)
>>                         ('browse hierarchy (h)'
>> spawnHierarchy)
>>                         ('browse protocol (p)'
>> browseFullProtocol)
>>                         -
>>                         ('printOut'
>> printOutClass)
>>                         ('fileOut'
>> fileOutClass)
>>                         -
>> +                       ('references... (r)'
>> browseVariableReferences)
>> +                       ('assignments... (a)'
>> browseVariableAssignments)
>> -                       ('inst var refs...'
>> browseInstVarRefs)
>> -                       ('inst var defs...'
>> browseInstVarDefs)
>> -                       ('class var refs...'
>> browseClassVarRefs)
>> -                       ('class vars'
>> browseClassVariables)
>>                         ('class refs (N)'
>> browseClassRefs)
>>                         -
>>                         ('more...'
>> offerShiftedClassListMenu))]
>>
>>                 ifTrue: [#(
>>                         -
>>                         ('unsent methods'
>> browseUnusedMethods)
>>                         ('unreferenced inst vars'
>> showUnreferencedInstVars)
>>                         ('unreferenced class vars'
>> showUnreferencedClassVars)
>>                         -
>>                         ('sample instance'
>> makeSampleInstance)
>>                         ('inspect instances'
>> inspectInstances)
>>                         ('inspect subinstances'
>> inspectSubInstances)
>>                         -
>>                         ('more...'
>> offerUnshiftedClassListMenu ))]).
>>         ^ aMenu!
>>
>> Item was changed:
>>   ----- Method: CodeHolder>>abbreviatedWordingFor: (in category
>> 'commands') -----
>>   abbreviatedWordingFor: aButtonSelector
>> +       "Answer the abbreviated form of wording, from a static table.
>> Answer nil if there is no entry -- in which case the long form will be used
>> on the corresponding browser button."
>> -       "Answer the abbreviated form of wording, from a static table which
>> you're welcome to edit.  Answer nil if there is no entry -- in which case
>> the long firm will be used on the corresponding browser button."
>>
>>         #(
>>         (browseMethodFull                               'browse')
>>         (browseSendersOfMessages                'senders')
>>         (browseMessages                         'impl')
>>         (browseVersions                                 'vers')
>>         (methodHierarchy                                'inher')
>>         (classHierarchy                                 'hier')
>> +       (browseVariableReferences                               'refs')
>> -       (browseInstVarRefs                              'iVar')
>> -       (browseClassVarRefs                             'cVar')
>>         (offerMenu                                              'menu'))
>> do:
>>
>>                 [:pair | pair first == aButtonSelector ifTrue: [^ pair
>> second]].
>>         ^ nil!
>>
>> Item was changed:
>>   ----- Method: CodeHolder>>messageListKey:from: (in category 'message
>> list menu') -----
>>   messageListKey: aChar from: view
>>         "Respond to a Command key.  I am a model with a code pane, and I
>> also
>>         have a listView that has a list of methods.  The view knows how to
>> get
>>         the list and selection."
>>
>>         | sel class |
>>         aChar == $D ifTrue: [^ self toggleDiffing].
>>
>>         sel := self selectedMessageName.
>>         aChar == $m ifTrue:  "These next two put up a type in if no
>> message selected"
>>                 [^ self useSelector: sel orGetSelectorAndSendQuery:
>> #browseAllImplementorsOf: to: self ].
>>         aChar == $n ifTrue:
>>                 [^ self useSelector: sel orGetSelectorAndSendQuery:
>> #browseAllCallsOn: to: self ].
>>
>>         "The following require a class selection"
>>         (class := self selectedClassOrMetaClass) ifNil: [^ self arrowKey:
>> aChar from: view].
>>         aChar == $b ifTrue: [^ Browser fullOnClass: class selector: sel].
>>         aChar == $N ifTrue: [^ self browseClassRefs].
>>         aChar == $i ifTrue: [^ self methodHierarchy].
>>         aChar == $h ifTrue: [^ self classHierarchy].
>>         aChar == $p ifTrue: [^ self browseFullProtocol].
>> +       aChar == $r ifTrue: [^ self browseVariableReferences].
>> +       aChar == $a ifTrue: [^ self browseVariableAssignments].
>>
>> +
>>         "The following require a method selection"
>>         sel ifNotNil:
>>                 [aChar == $o ifTrue: [^ self fileOutMessage].
>>                 aChar == $c ifTrue: [^ self copySelector].
>>                 aChar == $v ifTrue: [^ self browseVersions].
>>                 aChar == $O ifTrue: [^ self openSingleMessageBrowser].
>>                 aChar == $x ifTrue: [^ self removeMessage].
>>                 aChar == $d ifTrue: [^ self removeMessageFromBrowser].
>>
>>                 (aChar == $C and: [self canShowMultipleMessageCategories])
>>                         ifTrue: [^ self showHomeCategory]].
>>
>>         ^ self arrowKey: aChar from: view!
>>
>> Item was changed:
>>   ----- Method: CodeHolder>>optionalButtonPairs (in category 'controls')
>> -----
>>   optionalButtonPairs
>>         "Answer a tuple (formerly pairs) defining buttons, in the format:
>>                         button label
>>                         selector to send
>>                         help message"
>>
>>         | aList |
>>
>>         aList := #(
>>         ('browse'                       browseMethodFull
>> 'view this method in a browser')
>>         ('senders'                      browseSendersOfMessages 'browse
>> senders of...')
>>         ('implementors'         browseMessages
>> 'browse implementors of...')
>>         ('versions'                     browseVersions
>> 'browse versions')),
>>
>>         (Preferences decorateBrowserButtons
>>                 ifTrue:
>>                         [{#('inheritance'               methodHierarchy
>> 'browse method inheritance
>>   green: sends to super
>>   tan: has override(s)
>>   mauve: both of the above
>>   pink: is an override but doesn''t call super
>>   pinkish tan: has override(s), also is an override but doesn''t call
>> super' )}]
>>                 ifFalse:
>>                         [{#('inheritance'               methodHierarchy
>> 'browse method inheritance')}]),
>>
>>         #(
>>         ('hierarchy'            classHierarchy
>> 'browse class hierarchy')
>> +       ('vars'                 browseVariableReferences
>> 'references...')).
>> -       ('inst vars'                    browseInstVarRefs
>> 'inst var refs...')
>> -       ('class vars'                   browseClassVarRefs
>> 'class var refs...')).
>>
>>         ^ aList!
>>
>> Item was added:
>> + ----- Method: CodeHolder>>receiverClass (in category 'toolbuilder')
>> -----
>> + receiverClass
>> +       ^ self selectedClassOrMetaClass !
>>
>> Item was added:
>> + ----- Method: Debugger>>classHierarchy (in category 'toolbuilder') -----
>> + classHierarchy
>> +       "Create and schedule a class list browser on the receiver's
>> hierarchy."
>> +       (self selectedMessageName = #doesNotUnderstand: and: [ self
>> selectedClassOrMetaClass = Object ])
>> +               ifTrue:
>> +                       [ self systemNavigation
>> +                               spawnHierarchyForClass: self receiverClass
>> +                               selector: self selectedMessageName ]
>> +               ifFalse: [ super classHierarchy ]!
>>
>> Item was changed:
>>   ----- Method: Debugger>>contextStackMenu:shifted: (in category 'context
>> stack menu') -----
>>   contextStackMenu: aMenu shifted: shifted
>>         "Set up the menu appropriately for the context-stack-list, either
>> shifted or unshifted as per the parameter provided"
>>
>>         ^ shifted ifFalse:[
>>                 aMenu addList: {
>>                         {'fullStack (f)'.               #fullStack}.
>>                         {'restart (r)'.         #restart}.
>>                         {'proceed (p)'.         #proceed}.
>>                         {'step (t)'.                    #doStep}.
>>                         {'step through (T)'.    #stepIntoBlock}.
>>                         {'send (e)'.                    #send}.
>>                         {'where (w)'.           #where}.
>>                         {'peel to first like this'.
>> #peelToFirst}.
>>                         #-.
>>                         {'return entered value'.
>> #returnValue}.
>>                         #-.
>>                         {'toggle break on entry'.
>> #toggleBreakOnEntry}.
>>                         {'senders of... (n)'.
>> #browseSendersOfMessages}.
>>                         {'implementors of... (m)'.      #browseMessages}.
>>                         {'inheritance (i)'.     #methodHierarchy}.
>>                         #-.
>>                         {'versions (v)'.                #browseVersions}.
>> -                       {'inst var refs...'.
>> #browseInstVarRefs}.
>>                         #-.
>> +                       {'references... (r)'.
>> #browseVariableReferences}.
>> +                       {'assignments... (a)'.
>> #browseVariableAssignments}.
>> -                       {'inst var defs...'.    #browseInstVarDefs}.
>> -                       {'class var refs...'.   #browseClassVarRefs}.
>> -                       {'class variables'.     #browseClassVariables}.
>>                         #-.
>>                         {'class refs (N)'.              #browseClassRefs}.
>>                         {'browse full (b)'.     #browseMethodFull}.
>>                         {'file out '.                   #fileOutMessage}.
>>                         #-.
>>                         {'mail out bug report'. #mailOutBugReport}.
>>                         {'more...'.
>> #shiftedYellowButtonActivity}.
>>                 }.
>>         ] ifTrue: [
>>                 aMenu addList: {
>>                         {'browse class hierarchy'.      #classHierarchy}.
>>                         {'browse class'.
>> #browseClass}.
>>                         {'browse method (O)'.
>> #openSingleMessageBrowser}.
>>                         {'implementors of sent messages'.
>> #browseAllMessages}.
>>                         {'change sets with this method'.
>> #findMethodInChangeSets}.
>>                         #-.
>>                         {'inspect instances'.
>> #inspectInstances}.
>>                         {'inspect subinstances'.
>> #inspectSubInstances}.
>>                         #-.
>>                         {'revert to previous version'.
>> #revertToPreviousVersion}.
>>                         {'remove from current change set'.
>> #removeFromCurrentChanges}.
>>                         {'revert & remove from changes'.
>> #revertAndForget}.
>>                         #-.
>>                         {'more...'.
>> #unshiftedYellowButtonActivity}.
>>                 }
>>         ].!
>>
>> Item was added:
>> + ----- Method: Debugger>>receiverClass (in category 'toolbuilder') -----
>> + receiverClass
>> +       ^ self selectedContext receiver class!
>>
>> Item was removed:
>> - ----- Method: Inspector>>classVarRefs (in category 'menu commands')
>> -----
>> - classVarRefs
>> -       "Request a browser of methods that store into a chosen instance
>> variable"
>> -
>> -       | aClass |
>> -       (aClass := self classOfSelection) ifNotNil:
>> -               [self systemNavigation  browseClassVarRefs: aClass].
>> - !
>>
>> Item was changed:
>>   ----- Method: Inspector>>fieldListMenu: (in category 'menu commands')
>> -----
>>   fieldListMenu: aMenu
>>         "Arm the supplied menu with items for the field-list of the
>> receiver"
>>
>>         aMenu addStayUpItemSpecial.
>>
>>         aMenu addList: #(
>>                 ('inspect (i)'
>> inspectSelection)
>>                 ('explore (I)'
>> exploreSelection)).
>>
>>         self addCollectionItemsTo: aMenu.
>>
>>         aMenu addList: #(
>>                 -
>>                 ('method refs to this inst var'
>> referencesToSelection)
>>                 ('methods storing into this inst var'   defsOfSelection)
>>                 ('objects pointing to this value'
>> objectReferencesToSelection)
>>                 ('chase pointers'
>> chasePointers)
>>                 ('explore pointers'
>> explorePointers)
>>                 -
>>                 ('browse full (b)'
>> browseMethodFull)
>>                 ('browse class'
>> browseClass)
>>                 ('browse hierarchy (h)'
>> classHierarchy)
>>                 ('browse protocol (p)'
>> browseFullProtocol)
>>                 -
>> +               ('references... (r)'
>> browseVariableReferences)
>> +               ('assignments... (a)'
>> browseVariableAssignments)
>> -               ('inst var refs...'
>> browseInstVarRefs)
>> -               ('inst var defs...'
>> browseInstVarDefs)
>> -               ('class var refs...'
>> classVarRefs)
>> -               ('class variables'
>> browseClassVariables)
>>                 ('class refs (N)'
>> browseClassRefs)
>>                 -
>>                 ('copy name (c)'
>> copyName)
>>                 ('basic inspect'
>> inspectBasic)).
>>
>>         Smalltalk isMorphic ifTrue:
>>                 [aMenu addList: #(
>>                         -
>>                         ('tile for this value   (t)'
>> tearOffTile)
>>                         ('viewer for this value (v)'
>> viewerForValue))].
>>
>>         ^ aMenu
>>
>>
>>   "                     -
>>                         ('alias for this value'
>> aliasForValue)
>>                         ('watcher for this slot'
>> watcherForSlot)"
>>
>>   !
>>
>> Item was changed:
>>   ----- Method: RecentMessageSet>>messageListMenu:shifted: (in category
>> 'message functions') -----
>>   messageListMenu: aMenu shifted: shifted
>>         "Answer the message-list menu"
>>
>>         shifted ifTrue: [^ self shiftedMessageListMenu: aMenu].
>>         aMenu addList:#(
>>                         ('what to show...'
>> offerWhatToShowMenu)
>>                         -
>>                         ('browse full (b)'
>> browseMethodFull)
>>                         ('browse hierarchy (h)'
>> classHierarchy)
>>                         ('browse method (O)'
>> openSingleMessageBrowser)
>>                         ('browse protocol (p)'
>> browseFullProtocol)
>>                         -
>>                         ('fileOut (o)'
>> fileOutMessage)
>>                         ('printOut'
>> printOutMessage)
>>                         ('copy selector (c)'
>> copySelector)
>>                         ('copy reference'
>> copyReference)
>>                         -
>>                         ('senders of... (n)'
>> browseSendersOfMessages)
>>                         ('implementors of... (m)'
>> browseMessages)
>>                         ('inheritance (i)'
>> methodHierarchy)
>>                         ('versions (v)'
>> browseVersions)
>>                         -
>> +                       ('references... (r)'
>> browseVariableReferences)
>> +                       ('assignments... (a)'
>> browseVariableAssignments)
>> -                       ('inst var refs...'
>> browseInstVarRefs)
>> -                       ('inst var defs...'
>> browseInstVarDefs)
>> -                       ('class var refs...'
>> browseClassVarRefs)
>> -                       ('class variables'
>> browseClassVariables)
>>                         ('class refs (N)'
>> browseClassRefs)
>>                         -
>>                         ('remove method (x)'
>> removeMessage)
>>                         ('remove from RecentSubmissions'
>> removeFromRecentSubmissions)
>>                         -
>>                         ('more...'
>> shiftedYellowButtonActivity)).
>>         ^ aMenu!
>>
>> Item was removed:
>> - ----- Method: StringHolder>>browseClassVarRefs (in category
>> '*Tools-traits') -----
>> - browseClassVarRefs
>> -       "1/17/96 sw: devolve responsibility to the class, so that the code
>> that does the real work can be shared"
>> -
>> -       | cls |
>> -       cls := self selectedClass.
>> -       (cls notNil and: [cls isTrait not])
>> -               ifTrue: [self systemNavigation  browseClassVarRefs: cls]!
>>
>> Item was removed:
>> - ----- Method: StringHolder>>browseClassVariables (in category
>> '*Tools-traits') -----
>> - browseClassVariables
>> -       "Browse the class variables of the selected class. 2/5/96 sw"
>> -       | cls |
>> -       cls := self selectedClass.
>> -       (cls notNil and: [cls isTrait not])
>> -               ifTrue: [self systemNavigation  browseClassVariables: cls]
>> - !
>>
>> Item was removed:
>> - ----- Method: StringHolder>>browseInstVarDefs (in category
>> '*Tools-traits') -----
>> - browseInstVarDefs
>> -
>> -       | cls |
>> -       cls := self selectedClassOrMetaClass.
>> -       (cls notNil and: [cls isTrait not])
>> -               ifTrue: [self systemNavigation browseInstVarDefs: cls]!
>>
>> Item was removed:
>> - ----- Method: StringHolder>>browseInstVarRefs (in category
>> '*Tools-traits') -----
>> - browseInstVarRefs
>> -       "1/26/96 sw: real work moved to class, so it can be shared"
>> -       | cls |
>> -       cls := self selectedClassOrMetaClass.
>> -       (cls notNil and: [cls isTrait not])
>> -               ifTrue: [self systemNavigation browseInstVarRefs: cls]!
>>
>> Item was added:
>> + ----- Method: StringHolder>>browseVariableAssignments (in category
>> '*Tools-traits') -----
>> + browseVariableAssignments
>> +       | cls |
>> +       cls := self selectedClassOrMetaClass.
>> +       (cls notNil and: [ cls isTrait not ]) ifTrue: [ self
>> systemNavigation browseVariableAssignments: cls ]!
>>
>> Item was added:
>> + ----- Method: StringHolder>>browseVariableReferences (in category
>> '*Tools-traits') -----
>> + browseVariableReferences
>> +       | cls |
>> +       cls := self selectedClassOrMetaClass.
>> +       (cls notNil and: [cls isTrait not])
>> +               ifTrue: [self systemNavigation browseVariableReferences:
>> cls]!
>>
>> Item was changed:
>>   ----- Method: StringHolder>>classListKey:from: (in category '*Tools')
>> -----
>>   classListKey: aChar from: view
>>         "Respond to a Command key.  I am a model with a list of classes
>> and a
>>         code pane, and I also have a listView that has a list of methods.
>> The
>>         view knows how to get the list and selection."
>>
>>         aChar == $f ifTrue: [^ self findMethod].
>> +       aChar == $r ifTrue: [^ self browseVariableReferences].
>> +       aChar == $a ifTrue: [^ self browseVariableAssignments].
>> -       aChar == $r ifTrue: [^ self browseInstVarRefs].
>> -       aChar == $d ifTrue: [^ self browseInstVarDefs].
>>         aChar == $h ifTrue: [^ self spawnHierarchy].
>>         aChar == $x ifTrue: [^ self removeClass].
>>         ^ self messageListKey: aChar from: view!
>>
>>
>
>
>
>


More information about the Squeak-dev mailing list