The Trunk: Tools-cmm.812.mcz

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

The Trunk: Tools-cmm.812.mcz

commits-2
Chris Muller uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-cmm.812.mcz

==================== Summary ====================

Name: Tools-cmm.812
Author: cmm
Time: 8 May 2018, 10:59:15.586524 pm
UUID: d05b5ccd-cc99-4f00-85b1-264218092ef2
Ancestors: Tools-dtl.811

- Integrate newly-defined classes into the hierarchy list of a HierarchyBrowser without muting the other classes.  If it's outside the hierarchy, spawn it in a new window.
- Bug reports can contain sensitive and/or private information (variable values), so use care when sending them electronically.  'copy bug report to clipboard' replaced 'mail out bug report' on the debugger menu.

=============== Diff against Tools-dtl.811 ===============

Item was changed:
  ----- Method: Browser>>defineClass:notifying: (in category 'class functions') -----
  defineClass: defString notifying: aController  
  "The receiver's textual content is a request to define a new class. The
  source code is defString. If any errors occur in compilation, notify
  aController."
  | oldClass class newClassName defTokens keywdIx envt |
  oldClass := self selectedClassOrMetaClass.
  defTokens := defString findTokens: Character separators.
 
  ((defTokens first = 'Trait' and: [defTokens second = 'named:'])
  or: [defTokens second = 'classTrait'])
  ifTrue: [^self defineTrait: defString notifying: aController].
 
  keywdIx := defTokens findFirst: [:x | x beginsWith: 'category'].
  envt := self selectedEnvironment.
  keywdIx := defTokens findFirst: [:x | '*subclass*' match: x].
  newClassName := (defTokens at: keywdIx+1) copyWithoutAll: '#()'.
  ((oldClass isNil or: [oldClass theNonMetaClass name asString ~= newClassName])
  and: [envt includesKey: newClassName asSymbol]) ifTrue:
  ["Attempting to define new class over existing one when
  not looking at the original one in this browser..."
  (self confirm: ((newClassName , ' is an existing class in this system.
  Redefining it might cause serious problems.
  Is this really what you want to do?') asText makeBoldFrom: 1 to: newClassName size))
  ifFalse: [^ false]].
  "ar 8/29/1999: Use oldClass superclass for defining oldClass
  since oldClass superclass knows the definerClass of oldClass."
  oldClass ifNotNil:[oldClass := oldClass superclass].
  class := envt beCurrentDuring:
  [oldClass subclassDefinerClass
  evaluate: defString
  in: envt
  notifying: aController
  logged: false].
  (class isKindOf: Behavior)
+ ifTrue: [self changed: #systemCategoryList; changed: #classList.
+ self clearUserEditFlag; spawnOrNavigateTo: class.
- ifTrue: [self changed: #systemCategoryList.
- self changed: #classList.
- self clearUserEditFlag.
- self setClass: class selector: nil.
- "self clearUserEditFlag; editClass."
  ^ true]
  ifFalse: [^ false]!

Item was added:
+ ----- Method: Browser>>spawnOrNavigateTo: (in category 'private') -----
+ spawnOrNavigateTo: aClass
+ self setClass: aClass selector: nil!

Item was changed:
  ----- Method: Debugger>>mainContextStackMenu: (in category 'context stack menu') -----
  mainContextStackMenu: aMenu
  "Set up the menu appropriately for the context-stack-list, unshifted"
  <contextStackMenuShifted: false>
  ^ 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)
  -
  ('references    (r)' browseVariableReferences)
  ('assignments    (a)' browseVariableAssignments)
  -
  ('class refs (N)' browseClassRefs)
  ('browse full (b)' browseMethodFull)
  ('file out ' fileOutMessage)
  -
+ ('copy bug report to clipboard' copyBugReportToClipboard));
- ('mail out bug report' mailOutBugReport)
- ('bug report to clipboard' copyBugReportToClipboard));
  yourself
  !

Item was changed:
  ----- Method: HierarchyBrowser>>setClass: (in category 'initialization') -----
+ setClass: aClass
+ self initHierarchyForClass: (centralClass ifNil: [ aClass ]).
+ super setClass: aClass!
- setClass: aClass
-
- self initHierarchyForClass: aClass.
- super setClass: aClass.!

Item was added:
+ ----- Method: HierarchyBrowser>>spawnOrNavigateTo: (in category 'private') -----
+ spawnOrNavigateTo: aClass
+ (aClass inheritsFrom: centralClass)
+ ifTrue: [ super spawnOrNavigateTo: aClass ]
+ ifFalse: [ self systemNavigation browseHierarchy: aClass ]!

Item was changed:
  ----- Method: HierarchyBrowser>>updateAfterClassChange (in category 'initialization') -----
  updateAfterClassChange
  "It is possible that some the classes comprising the hierarchy have changed, so reinitialize the entire browser."
 
+ | priorSelection |
+ priorSelection := self selectedClassName.
+
  (centralClass notNil and: [centralClass isObsolete not])
+ ifTrue: [self initHierarchyForClass: centralClass].
+
+ (self classListIndexOf: priorSelection) > 0
+ ifTrue: [self selectClassNamed: priorSelection].!
- ifTrue: [self initHierarchyForClass: centralClass]!


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Tools-cmm.812.mcz

Eliot Miranda-2
Hi Chris,

    two things.  First this is an opportunity to replace  (class isKindOf: Behavior) with class isBehavior.  Second, why delete mail out bug report?  It's still useful right?

On Tue, May 8, 2018 at 8:59 PM, <[hidden email]> wrote:
Chris Muller uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-cmm.812.mcz

==================== Summary ====================

Name: Tools-cmm.812
Author: cmm
Time: 8 May 2018, 10:59:15.586524 pm
UUID: d05b5ccd-cc99-4f00-85b1-264218092ef2
Ancestors: Tools-dtl.811

- Integrate newly-defined classes into the hierarchy list of a HierarchyBrowser without muting the other classes.  If it's outside the hierarchy, spawn it in a new window.
- Bug reports can contain sensitive and/or private information (variable values), so use care when sending them electronically.  'copy bug report to clipboard' replaced 'mail out bug report' on the debugger menu.

=============== Diff against Tools-dtl.811 ===============

Item was changed:
  ----- Method: Browser>>defineClass:notifying: (in category 'class functions') -----
  defineClass: defString notifying: aController 
        "The receiver's textual content is a request to define a new class. The
        source code is defString. If any errors occur in compilation, notify
        aController."
        | oldClass class newClassName defTokens keywdIx envt |
        oldClass := self selectedClassOrMetaClass.
        defTokens := defString findTokens: Character separators.

        ((defTokens first = 'Trait' and: [defTokens second = 'named:'])
                or: [defTokens second = 'classTrait'])
                ifTrue: [^self defineTrait: defString notifying: aController].

        keywdIx := defTokens findFirst: [:x | x beginsWith: 'category'].
        envt := self selectedEnvironment.
        keywdIx := defTokens findFirst: [:x | '*subclass*' match: x].
        newClassName := (defTokens at: keywdIx+1) copyWithoutAll: '#()'.
        ((oldClass isNil or: [oldClass theNonMetaClass name asString ~= newClassName])
                and: [envt includesKey: newClassName asSymbol]) ifTrue:
                        ["Attempting to define new class over existing one when
                                not looking at the original one in this browser..."
                        (self confirm: ((newClassName , ' is an existing class in this system.
  Redefining it might cause serious problems.
  Is this really what you want to do?') asText makeBoldFrom: 1 to: newClassName size))
                                ifFalse: [^ false]].
        "ar 8/29/1999: Use oldClass superclass for defining oldClass
        since oldClass superclass knows the definerClass of oldClass."
        oldClass ifNotNil:[oldClass := oldClass superclass].
        class := envt beCurrentDuring:
                [oldClass subclassDefinerClass
                                evaluate: defString
                                in: envt
                                notifying: aController
                                logged: false].
        (class isKindOf: Behavior)
+               ifTrue: [self changed: #systemCategoryList; changed: #classList.
+                               self clearUserEditFlag; spawnOrNavigateTo: class.
-               ifTrue: [self changed: #systemCategoryList.
-                               self changed: #classList.
-                               self clearUserEditFlag.
-                               self setClass: class selector: nil.
-                               "self clearUserEditFlag; editClass."
                                ^ true]
                ifFalse: [^ false]!

Item was added:
+ ----- Method: Browser>>spawnOrNavigateTo: (in category 'private') -----
+ spawnOrNavigateTo: aClass
+       self setClass: aClass selector: nil!

Item was changed:
  ----- Method: Debugger>>mainContextStackMenu: (in category 'context stack menu') -----
  mainContextStackMenu: aMenu
        "Set up the menu appropriately for the context-stack-list, unshifted"
        <contextStackMenuShifted: false>
        ^ 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)
                        -
                        ('references    (r)'                    browseVariableReferences)
                        ('assignments    (a)'           browseVariableAssignments)
                        -
                        ('class refs (N)'                               browseClassRefs)
                        ('browse full (b)'                      browseMethodFull)
                        ('file out '                                    fileOutMessage)
                        -
+                       ('copy bug report to clipboard' copyBugReportToClipboard));
-                       ('mail out bug report'          mailOutBugReport)
-                       ('bug report to clipboard'      copyBugReportToClipboard));
                yourself
  !

Item was changed:
  ----- Method: HierarchyBrowser>>setClass: (in category 'initialization') -----
+ setClass: aClass
+       self initHierarchyForClass: (centralClass ifNil: [ aClass ]).
+       super setClass: aClass!
- setClass: aClass
-
-       self initHierarchyForClass: aClass.
-       super setClass: aClass.!

Item was added:
+ ----- Method: HierarchyBrowser>>spawnOrNavigateTo: (in category 'private') -----
+ spawnOrNavigateTo: aClass
+       (aClass inheritsFrom: centralClass)
+               ifTrue: [ super spawnOrNavigateTo: aClass ]
+               ifFalse: [ self systemNavigation browseHierarchy: aClass ]!

Item was changed:
  ----- Method: HierarchyBrowser>>updateAfterClassChange (in category 'initialization') -----
  updateAfterClassChange
        "It is possible that some the classes comprising the hierarchy have changed, so reinitialize the entire browser."

+       | priorSelection |
+       priorSelection := self selectedClassName.
+       
        (centralClass notNil and: [centralClass isObsolete not])
+               ifTrue: [self initHierarchyForClass: centralClass].
+               
+       (self classListIndexOf: priorSelection) > 0
+               ifTrue: [self selectClassNamed: priorSelection].!
-               ifTrue: [self initHierarchyForClass: centralClass]!





--
_,,,^..^,,,_
best, Eliot


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Tools-cmm.812.mcz

timrowledge


> On 08-05-2018, at 10:30 PM, Eliot Miranda <[hidden email]> wrote:
> Second, why delete mail out bug report?  It's still useful right?

Not really - it's only of any value for a very small number of cases where someone has email set up in the image. I guess it's one of those places where an email package might provide a service and the menu stuff would reflect that. In general a copy-to-clipboard and use of your normal mail program is more useful


tim
--
tim Rowledge; [hidden email]; http://www.rowledge.org/tim
Fractured Idiom:- APRES MOE LE DELUGE - Larry and Curly get wet



Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Tools-cmm.812.mcz

Chris Muller-3
In reply to this post by Eliot Miranda-2
Hi Eliot,

>     two things.  First this is an opportunity to replace  (class isKindOf:
> Behavior) with class isBehavior.

Indeed, I wish I'd noticed that while I was in there.  I'll see if any
other review comments pop up, before committing a new version.

> Second, why delete mail out bug report?
> It's still useful right?

Not really, either menu option puts the user within just a couple of
gestures of sending an email, so having both is fairly redundant.
This is a good opportunity to reduce the dependency coupling between
the debugger and emailing functionality, and possibly slightly improve
safety from accidentally sending sensitive information in an email
(since cutting and pasting contents of an email requires a more
separate, deliberate action, than "send a bug report", which sounds
totally innocent, but possibly encourage the user to not need to
scrutinize it for sensitive data).  That may seem like over-thinking
it, but the one day it happens could lead to "headlines," :)  so I
almost feel a warning to that effect before the stack trace would be a
good reminder...


> On Tue, May 8, 2018 at 8:59 PM, <[hidden email]> wrote:
>>
>> Chris Muller uploaded a new version of Tools to project The Trunk:
>> http://source.squeak.org/trunk/Tools-cmm.812.mcz
>>
>> ==================== Summary ====================
>>
>> Name: Tools-cmm.812
>> Author: cmm
>> Time: 8 May 2018, 10:59:15.586524 pm
>> UUID: d05b5ccd-cc99-4f00-85b1-264218092ef2
>> Ancestors: Tools-dtl.811
>>
>> - Integrate newly-defined classes into the hierarchy list of a
>> HierarchyBrowser without muting the other classes.  If it's outside the
>> hierarchy, spawn it in a new window.
>> - Bug reports can contain sensitive and/or private information (variable
>> values), so use care when sending them electronically.  'copy bug report to
>> clipboard' replaced 'mail out bug report' on the debugger menu.
>>
>> =============== Diff against Tools-dtl.811 ===============
>>
>> Item was changed:
>>   ----- Method: Browser>>defineClass:notifying: (in category 'class
>> functions') -----
>>   defineClass: defString notifying: aController
>>         "The receiver's textual content is a request to define a new
>> class. The
>>         source code is defString. If any errors occur in compilation,
>> notify
>>         aController."
>>         | oldClass class newClassName defTokens keywdIx envt |
>>         oldClass := self selectedClassOrMetaClass.
>>         defTokens := defString findTokens: Character separators.
>>
>>         ((defTokens first = 'Trait' and: [defTokens second = 'named:'])
>>                 or: [defTokens second = 'classTrait'])
>>                 ifTrue: [^self defineTrait: defString notifying:
>> aController].
>>
>>         keywdIx := defTokens findFirst: [:x | x beginsWith: 'category'].
>>         envt := self selectedEnvironment.
>>         keywdIx := defTokens findFirst: [:x | '*subclass*' match: x].
>>         newClassName := (defTokens at: keywdIx+1) copyWithoutAll: '#()'.
>>         ((oldClass isNil or: [oldClass theNonMetaClass name asString ~=
>> newClassName])
>>                 and: [envt includesKey: newClassName asSymbol]) ifTrue:
>>                         ["Attempting to define new class over existing one
>> when
>>                                 not looking at the original one in this
>> browser..."
>>                         (self confirm: ((newClassName , ' is an existing
>> class in this system.
>>   Redefining it might cause serious problems.
>>   Is this really what you want to do?') asText makeBoldFrom: 1 to:
>> newClassName size))
>>                                 ifFalse: [^ false]].
>>         "ar 8/29/1999: Use oldClass superclass for defining oldClass
>>         since oldClass superclass knows the definerClass of oldClass."
>>         oldClass ifNotNil:[oldClass := oldClass superclass].
>>         class := envt beCurrentDuring:
>>                 [oldClass subclassDefinerClass
>>                                 evaluate: defString
>>                                 in: envt
>>                                 notifying: aController
>>                                 logged: false].
>>         (class isKindOf: Behavior)
>> +               ifTrue: [self changed: #systemCategoryList; changed:
>> #classList.
>> +                               self clearUserEditFlag; spawnOrNavigateTo:
>> class.
>> -               ifTrue: [self changed: #systemCategoryList.
>> -                               self changed: #classList.
>> -                               self clearUserEditFlag.
>> -                               self setClass: class selector: nil.
>> -                               "self clearUserEditFlag; editClass."
>>                                 ^ true]
>>                 ifFalse: [^ false]!
>>
>> Item was added:
>> + ----- Method: Browser>>spawnOrNavigateTo: (in category 'private') -----
>> + spawnOrNavigateTo: aClass
>> +       self setClass: aClass selector: nil!
>>
>> Item was changed:
>>   ----- Method: Debugger>>mainContextStackMenu: (in category 'context
>> stack menu') -----
>>   mainContextStackMenu: aMenu
>>         "Set up the menu appropriately for the context-stack-list,
>> unshifted"
>>         <contextStackMenuShifted: false>
>>         ^ 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)
>>                         -
>>                         ('references    (r)'
>> browseVariableReferences)
>>                         ('assignments    (a)'
>> browseVariableAssignments)
>>                         -
>>                         ('class refs (N)'
>> browseClassRefs)
>>                         ('browse full (b)'
>> browseMethodFull)
>>                         ('file out '
>> fileOutMessage)
>>                         -
>> +                       ('copy bug report to clipboard'
>> copyBugReportToClipboard));
>> -                       ('mail out bug report'          mailOutBugReport)
>> -                       ('bug report to clipboard'
>> copyBugReportToClipboard));
>>                 yourself
>>   !
>>
>> Item was changed:
>>   ----- Method: HierarchyBrowser>>setClass: (in category 'initialization')
>> -----
>> + setClass: aClass
>> +       self initHierarchyForClass: (centralClass ifNil: [ aClass ]).
>> +       super setClass: aClass!
>> - setClass: aClass
>> -
>> -       self initHierarchyForClass: aClass.
>> -       super setClass: aClass.!
>>
>> Item was added:
>> + ----- Method: HierarchyBrowser>>spawnOrNavigateTo: (in category
>> 'private') -----
>> + spawnOrNavigateTo: aClass
>> +       (aClass inheritsFrom: centralClass)
>> +               ifTrue: [ super spawnOrNavigateTo: aClass ]
>> +               ifFalse: [ self systemNavigation browseHierarchy: aClass
>> ]!
>>
>> Item was changed:
>>   ----- Method: HierarchyBrowser>>updateAfterClassChange (in category
>> 'initialization') -----
>>   updateAfterClassChange
>>         "It is possible that some the classes comprising the hierarchy
>> have changed, so reinitialize the entire browser."
>>
>> +       | priorSelection |
>> +       priorSelection := self selectedClassName.
>> +
>>         (centralClass notNil and: [centralClass isObsolete not])
>> +               ifTrue: [self initHierarchyForClass: centralClass].
>> +
>> +       (self classListIndexOf: priorSelection) > 0
>> +               ifTrue: [self selectClassNamed: priorSelection].!
>> -               ifTrue: [self initHierarchyForClass: centralClass]!
>>
>>
>
>
>
> --
> _,,,^..^,,,_
> best, Eliot
>
>
>

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Tools-cmm.812.mcz

Chris Muller-3
It appears I forgot to delete the mailout bug report method, too...
but is it okay to remove or should it be deprecated?  Only one sender,
so I think remove, but Marcel may prefer deprecation.  Marcel?

I can take care of that isKindOf: while I'm there...


On Wed, May 9, 2018 at 12:45 PM, Chris Muller <[hidden email]> wrote:

> Hi Eliot,
>
>>     two things.  First this is an opportunity to replace  (class isKindOf:
>> Behavior) with class isBehavior.
>
> Indeed, I wish I'd noticed that while I was in there.  I'll see if any
> other review comments pop up, before committing a new version.
>
>> Second, why delete mail out bug report?
>> It's still useful right?
>
> Not really, either menu option puts the user within just a couple of
> gestures of sending an email, so having both is fairly redundant.
> This is a good opportunity to reduce the dependency coupling between
> the debugger and emailing functionality, and possibly slightly improve
> safety from accidentally sending sensitive information in an email
> (since cutting and pasting contents of an email requires a more
> separate, deliberate action, than "send a bug report", which sounds
> totally innocent, but possibly encourage the user to not need to
> scrutinize it for sensitive data).  That may seem like over-thinking
> it, but the one day it happens could lead to "headlines," :)  so I
> almost feel a warning to that effect before the stack trace would be a
> good reminder...
>
>
>> On Tue, May 8, 2018 at 8:59 PM, <[hidden email]> wrote:
>>>
>>> Chris Muller uploaded a new version of Tools to project The Trunk:
>>> http://source.squeak.org/trunk/Tools-cmm.812.mcz
>>>
>>> ==================== Summary ====================
>>>
>>> Name: Tools-cmm.812
>>> Author: cmm
>>> Time: 8 May 2018, 10:59:15.586524 pm
>>> UUID: d05b5ccd-cc99-4f00-85b1-264218092ef2
>>> Ancestors: Tools-dtl.811
>>>
>>> - Integrate newly-defined classes into the hierarchy list of a
>>> HierarchyBrowser without muting the other classes.  If it's outside the
>>> hierarchy, spawn it in a new window.
>>> - Bug reports can contain sensitive and/or private information (variable
>>> values), so use care when sending them electronically.  'copy bug report to
>>> clipboard' replaced 'mail out bug report' on the debugger menu.
>>>
>>> =============== Diff against Tools-dtl.811 ===============
>>>
>>> Item was changed:
>>>   ----- Method: Browser>>defineClass:notifying: (in category 'class
>>> functions') -----
>>>   defineClass: defString notifying: aController
>>>         "The receiver's textual content is a request to define a new
>>> class. The
>>>         source code is defString. If any errors occur in compilation,
>>> notify
>>>         aController."
>>>         | oldClass class newClassName defTokens keywdIx envt |
>>>         oldClass := self selectedClassOrMetaClass.
>>>         defTokens := defString findTokens: Character separators.
>>>
>>>         ((defTokens first = 'Trait' and: [defTokens second = 'named:'])
>>>                 or: [defTokens second = 'classTrait'])
>>>                 ifTrue: [^self defineTrait: defString notifying:
>>> aController].
>>>
>>>         keywdIx := defTokens findFirst: [:x | x beginsWith: 'category'].
>>>         envt := self selectedEnvironment.
>>>         keywdIx := defTokens findFirst: [:x | '*subclass*' match: x].
>>>         newClassName := (defTokens at: keywdIx+1) copyWithoutAll: '#()'.
>>>         ((oldClass isNil or: [oldClass theNonMetaClass name asString ~=
>>> newClassName])
>>>                 and: [envt includesKey: newClassName asSymbol]) ifTrue:
>>>                         ["Attempting to define new class over existing one
>>> when
>>>                                 not looking at the original one in this
>>> browser..."
>>>                         (self confirm: ((newClassName , ' is an existing
>>> class in this system.
>>>   Redefining it might cause serious problems.
>>>   Is this really what you want to do?') asText makeBoldFrom: 1 to:
>>> newClassName size))
>>>                                 ifFalse: [^ false]].
>>>         "ar 8/29/1999: Use oldClass superclass for defining oldClass
>>>         since oldClass superclass knows the definerClass of oldClass."
>>>         oldClass ifNotNil:[oldClass := oldClass superclass].
>>>         class := envt beCurrentDuring:
>>>                 [oldClass subclassDefinerClass
>>>                                 evaluate: defString
>>>                                 in: envt
>>>                                 notifying: aController
>>>                                 logged: false].
>>>         (class isKindOf: Behavior)
>>> +               ifTrue: [self changed: #systemCategoryList; changed:
>>> #classList.
>>> +                               self clearUserEditFlag; spawnOrNavigateTo:
>>> class.
>>> -               ifTrue: [self changed: #systemCategoryList.
>>> -                               self changed: #classList.
>>> -                               self clearUserEditFlag.
>>> -                               self setClass: class selector: nil.
>>> -                               "self clearUserEditFlag; editClass."
>>>                                 ^ true]
>>>                 ifFalse: [^ false]!
>>>
>>> Item was added:
>>> + ----- Method: Browser>>spawnOrNavigateTo: (in category 'private') -----
>>> + spawnOrNavigateTo: aClass
>>> +       self setClass: aClass selector: nil!
>>>
>>> Item was changed:
>>>   ----- Method: Debugger>>mainContextStackMenu: (in category 'context
>>> stack menu') -----
>>>   mainContextStackMenu: aMenu
>>>         "Set up the menu appropriately for the context-stack-list,
>>> unshifted"
>>>         <contextStackMenuShifted: false>
>>>         ^ 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)
>>>                         -
>>>                         ('references    (r)'
>>> browseVariableReferences)
>>>                         ('assignments    (a)'
>>> browseVariableAssignments)
>>>                         -
>>>                         ('class refs (N)'
>>> browseClassRefs)
>>>                         ('browse full (b)'
>>> browseMethodFull)
>>>                         ('file out '
>>> fileOutMessage)
>>>                         -
>>> +                       ('copy bug report to clipboard'
>>> copyBugReportToClipboard));
>>> -                       ('mail out bug report'          mailOutBugReport)
>>> -                       ('bug report to clipboard'
>>> copyBugReportToClipboard));
>>>                 yourself
>>>   !
>>>
>>> Item was changed:
>>>   ----- Method: HierarchyBrowser>>setClass: (in category 'initialization')
>>> -----
>>> + setClass: aClass
>>> +       self initHierarchyForClass: (centralClass ifNil: [ aClass ]).
>>> +       super setClass: aClass!
>>> - setClass: aClass
>>> -
>>> -       self initHierarchyForClass: aClass.
>>> -       super setClass: aClass.!
>>>
>>> Item was added:
>>> + ----- Method: HierarchyBrowser>>spawnOrNavigateTo: (in category
>>> 'private') -----
>>> + spawnOrNavigateTo: aClass
>>> +       (aClass inheritsFrom: centralClass)
>>> +               ifTrue: [ super spawnOrNavigateTo: aClass ]
>>> +               ifFalse: [ self systemNavigation browseHierarchy: aClass
>>> ]!
>>>
>>> Item was changed:
>>>   ----- Method: HierarchyBrowser>>updateAfterClassChange (in category
>>> 'initialization') -----
>>>   updateAfterClassChange
>>>         "It is possible that some the classes comprising the hierarchy
>>> have changed, so reinitialize the entire browser."
>>>
>>> +       | priorSelection |
>>> +       priorSelection := self selectedClassName.
>>> +
>>>         (centralClass notNil and: [centralClass isObsolete not])
>>> +               ifTrue: [self initHierarchyForClass: centralClass].
>>> +
>>> +       (self classListIndexOf: priorSelection) > 0
>>> +               ifTrue: [self selectClassNamed: priorSelection].!
>>> -               ifTrue: [self initHierarchyForClass: centralClass]!
>>>
>>>
>>
>>
>>
>> --
>> _,,,^..^,,,_
>> best, Eliot
>>
>>
>>

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Tools-cmm.812.mcz

Eliot Miranda-2
Hi Chris,

On Wed, May 9, 2018 at 10:49 AM, Chris Muller <[hidden email]> wrote:
It appears I forgot to delete the mailout bug report method, too...
but is it okay to remove or should it be deprecated?  Only one sender,
so I think remove, but Marcel may prefer deprecation.  Marcel?

My inclination would be to keep it as a nice example of sending email in Squeak, and I would address Tim' criticism by making sure that setting up email preferences was easy.  Being able to send email isn't widely used but it is very useful in some circumstances.  Either email is in an well supported or out in its own package.  Arguably, what we have is sitting on the fence.
 

I can take care of that isKindOf: while I'm there...

Thanks!
 


On Wed, May 9, 2018 at 12:45 PM, Chris Muller <[hidden email]> wrote:
> Hi Eliot,
>
>>     two things.  First this is an opportunity to replace  (class isKindOf:
>> Behavior) with class isBehavior.
>
> Indeed, I wish I'd noticed that while I was in there.  I'll see if any
> other review comments pop up, before committing a new version.
>
>> Second, why delete mail out bug report?
>> It's still useful right?
>
> Not really, either menu option puts the user within just a couple of
> gestures of sending an email, so having both is fairly redundant.
> This is a good opportunity to reduce the dependency coupling between
> the debugger and emailing functionality, and possibly slightly improve
> safety from accidentally sending sensitive information in an email
> (since cutting and pasting contents of an email requires a more
> separate, deliberate action, than "send a bug report", which sounds
> totally innocent, but possibly encourage the user to not need to
> scrutinize it for sensitive data).  That may seem like over-thinking
> it, but the one day it happens could lead to "headlines," :)  so I
> almost feel a warning to that effect before the stack trace would be a
> good reminder...
>
>
>> On Tue, May 8, 2018 at 8:59 PM, <[hidden email]> wrote:
>>>
>>> Chris Muller uploaded a new version of Tools to project The Trunk:
>>> http://source.squeak.org/trunk/Tools-cmm.812.mcz
>>>
>>> ==================== Summary ====================
>>>
>>> Name: Tools-cmm.812
>>> Author: cmm
>>> Time: 8 May 2018, 10:59:15.586524 pm
>>> UUID: d05b5ccd-cc99-4f00-85b1-264218092ef2
>>> Ancestors: Tools-dtl.811
>>>
>>> - Integrate newly-defined classes into the hierarchy list of a
>>> HierarchyBrowser without muting the other classes.  If it's outside the
>>> hierarchy, spawn it in a new window.
>>> - Bug reports can contain sensitive and/or private information (variable
>>> values), so use care when sending them electronically.  'copy bug report to
>>> clipboard' replaced 'mail out bug report' on the debugger menu.
>>>
>>> =============== Diff against Tools-dtl.811 ===============
>>>
>>> Item was changed:
>>>   ----- Method: Browser>>defineClass:notifying: (in category 'class
>>> functions') -----
>>>   defineClass: defString notifying: aController
>>>         "The receiver's textual content is a request to define a new
>>> class. The
>>>         source code is defString. If any errors occur in compilation,
>>> notify
>>>         aController."
>>>         | oldClass class newClassName defTokens keywdIx envt |
>>>         oldClass := self selectedClassOrMetaClass.
>>>         defTokens := defString findTokens: Character separators.
>>>
>>>         ((defTokens first = 'Trait' and: [defTokens second = 'named:'])
>>>                 or: [defTokens second = 'classTrait'])
>>>                 ifTrue: [^self defineTrait: defString notifying:
>>> aController].
>>>
>>>         keywdIx := defTokens findFirst: [:x | x beginsWith: 'category'].
>>>         envt := self selectedEnvironment.
>>>         keywdIx := defTokens findFirst: [:x | '*subclass*' match: x].
>>>         newClassName := (defTokens at: keywdIx+1) copyWithoutAll: '#()'.
>>>         ((oldClass isNil or: [oldClass theNonMetaClass name asString ~=
>>> newClassName])
>>>                 and: [envt includesKey: newClassName asSymbol]) ifTrue:
>>>                         ["Attempting to define new class over existing one
>>> when
>>>                                 not looking at the original one in this
>>> browser..."
>>>                         (self confirm: ((newClassName , ' is an existing
>>> class in this system.
>>>   Redefining it might cause serious problems.
>>>   Is this really what you want to do?') asText makeBoldFrom: 1 to:
>>> newClassName size))
>>>                                 ifFalse: [^ false]].
>>>         "ar 8/29/1999: Use oldClass superclass for defining oldClass
>>>         since oldClass superclass knows the definerClass of oldClass."
>>>         oldClass ifNotNil:[oldClass := oldClass superclass].
>>>         class := envt beCurrentDuring:
>>>                 [oldClass subclassDefinerClass
>>>                                 evaluate: defString
>>>                                 in: envt
>>>                                 notifying: aController
>>>                                 logged: false].
>>>         (class isKindOf: Behavior)
>>> +               ifTrue: [self changed: #systemCategoryList; changed:
>>> #classList.
>>> +                               self clearUserEditFlag; spawnOrNavigateTo:
>>> class.
>>> -               ifTrue: [self changed: #systemCategoryList.
>>> -                               self changed: #classList.
>>> -                               self clearUserEditFlag.
>>> -                               self setClass: class selector: nil.
>>> -                               "self clearUserEditFlag; editClass."
>>>                                 ^ true]
>>>                 ifFalse: [^ false]!
>>>
>>> Item was added:
>>> + ----- Method: Browser>>spawnOrNavigateTo: (in category 'private') -----
>>> + spawnOrNavigateTo: aClass
>>> +       self setClass: aClass selector: nil!
>>>
>>> Item was changed:
>>>   ----- Method: Debugger>>mainContextStackMenu: (in category 'context
>>> stack menu') -----
>>>   mainContextStackMenu: aMenu
>>>         "Set up the menu appropriately for the context-stack-list,
>>> unshifted"
>>>         <contextStackMenuShifted: false>
>>>         ^ 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)
>>>                         -
>>>                         ('references    (r)'
>>> browseVariableReferences)
>>>                         ('assignments    (a)'
>>> browseVariableAssignments)
>>>                         -
>>>                         ('class refs (N)'
>>> browseClassRefs)
>>>                         ('browse full (b)'
>>> browseMethodFull)
>>>                         ('file out '
>>> fileOutMessage)
>>>                         -
>>> +                       ('copy bug report to clipboard'
>>> copyBugReportToClipboard));
>>> -                       ('mail out bug report'          mailOutBugReport)
>>> -                       ('bug report to clipboard'
>>> copyBugReportToClipboard));
>>>                 yourself
>>>   !
>>>
>>> Item was changed:
>>>   ----- Method: HierarchyBrowser>>setClass: (in category 'initialization')
>>> -----
>>> + setClass: aClass
>>> +       self initHierarchyForClass: (centralClass ifNil: [ aClass ]).
>>> +       super setClass: aClass!
>>> - setClass: aClass
>>> -
>>> -       self initHierarchyForClass: aClass.
>>> -       super setClass: aClass.!
>>>
>>> Item was added:
>>> + ----- Method: HierarchyBrowser>>spawnOrNavigateTo: (in category
>>> 'private') -----
>>> + spawnOrNavigateTo: aClass
>>> +       (aClass inheritsFrom: centralClass)
>>> +               ifTrue: [ super spawnOrNavigateTo: aClass ]
>>> +               ifFalse: [ self systemNavigation browseHierarchy: aClass
>>> ]!
>>>
>>> Item was changed:
>>>   ----- Method: HierarchyBrowser>>updateAfterClassChange (in category
>>> 'initialization') -----
>>>   updateAfterClassChange
>>>         "It is possible that some the classes comprising the hierarchy
>>> have changed, so reinitialize the entire browser."
>>>
>>> +       | priorSelection |
>>> +       priorSelection := self selectedClassName.
>>> +
>>>         (centralClass notNil and: [centralClass isObsolete not])
>>> +               ifTrue: [self initHierarchyForClass: centralClass].
>>> +
>>> +       (self classListIndexOf: priorSelection) > 0
>>> +               ifTrue: [self selectClassNamed: priorSelection].!
>>> -               ifTrue: [self initHierarchyForClass: centralClass]!
>>>
>>>
>>
>>
>>
>> --
>> _,,,^..^,,,_
>> best, Eliot
>>
>>
>>




--
_,,,^..^,,,_
best, Eliot


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Tools-cmm.812.mcz

Tim Johnson-2

On May 9, 2018, at 10:59 AM, Eliot Miranda <[hidden email]> wrote:

My inclination would be to keep it as a nice example of sending email in Squeak, and I would address Tim' criticism by making sure that setting up email preferences was easy.  Being able to send email isn't widely used but it is very useful in some circumstances.  Either email is in an well supported or out in its own package.  Arguably, what we have is sitting on the fence.

As far back as 2008, people who posted bugs to the mailing list using this feature were welcomed into the community by a reply encouraging  them not to use the feature anymore and to instead submit bugs using Mantis.  ;)


But, of course, times and tastes change. 

It could be a simple, helpful gesture to prepend something like the following to Debugger>>#mailOutBugReport :

UIManager confirm: 'You are about to send a bug report to the mailing list.\This could potentially expose sensitive data to outside parties.\Additionally, this feature is rarely used.\Proceed?' withCRs

Thanks,
Tim




Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Tools-cmm.812.mcz

Chris Muller-3
In reply to this post by Eliot Miranda-2
Another idea would be to check whether mail is "set up" (Service
present and set up with valid values) when building that menu and, if
so, present the mail out option otherwise the clipboard option.

>> It appears I forgot to delete the mailout bug report method, too...
>> but is it okay to remove or should it be deprecated?  Only one sender,
>> so I think remove, but Marcel may prefer deprecation.  Marcel?
>
> My inclination would be to keep it as a nice example of sending email in
> Squeak,

Mine, too, but we should move it to somewhere in the Mail package
(whatever it is, sorry, not in front of an image right now).

> and I would address Tim' criticism by making sure that setting up
> email preferences was easy.  Being able to send email isn't widely used but
> it is very useful in some circumstances.  Either email is in an well
> supported or out in its own package.  Arguably, what we have is sitting on
> the fence.
>
>>
>>
>> I can take care of that isKindOf: while I'm there...
>
>
> Thanks!
>
>>
>>
>>
>> On Wed, May 9, 2018 at 12:45 PM, Chris Muller <[hidden email]> wrote:
>> > Hi Eliot,
>> >
>> >>     two things.  First this is an opportunity to replace  (class
>> >> isKindOf:
>> >> Behavior) with class isBehavior.
>> >
>> > Indeed, I wish I'd noticed that while I was in there.  I'll see if any
>> > other review comments pop up, before committing a new version.
>> >
>> >> Second, why delete mail out bug report?
>> >> It's still useful right?
>> >
>> > Not really, either menu option puts the user within just a couple of
>> > gestures of sending an email, so having both is fairly redundant.
>> > This is a good opportunity to reduce the dependency coupling between
>> > the debugger and emailing functionality, and possibly slightly improve
>> > safety from accidentally sending sensitive information in an email
>> > (since cutting and pasting contents of an email requires a more
>> > separate, deliberate action, than "send a bug report", which sounds
>> > totally innocent, but possibly encourage the user to not need to
>> > scrutinize it for sensitive data).  That may seem like over-thinking
>> > it, but the one day it happens could lead to "headlines," :)  so I
>> > almost feel a warning to that effect before the stack trace would be a
>> > good reminder...
>> >
>> >
>> >> On Tue, May 8, 2018 at 8:59 PM, <[hidden email]> wrote:
>> >>>
>> >>> Chris Muller uploaded a new version of Tools to project The Trunk:
>> >>> http://source.squeak.org/trunk/Tools-cmm.812.mcz
>> >>>
>> >>> ==================== Summary ====================
>> >>>
>> >>> Name: Tools-cmm.812
>> >>> Author: cmm
>> >>> Time: 8 May 2018, 10:59:15.586524 pm
>> >>> UUID: d05b5ccd-cc99-4f00-85b1-264218092ef2
>> >>> Ancestors: Tools-dtl.811
>> >>>
>> >>> - Integrate newly-defined classes into the hierarchy list of a
>> >>> HierarchyBrowser without muting the other classes.  If it's outside
>> >>> the
>> >>> hierarchy, spawn it in a new window.
>> >>> - Bug reports can contain sensitive and/or private information
>> >>> (variable
>> >>> values), so use care when sending them electronically.  'copy bug
>> >>> report to
>> >>> clipboard' replaced 'mail out bug report' on the debugger menu.
>> >>>
>> >>> =============== Diff against Tools-dtl.811 ===============
>> >>>
>> >>> Item was changed:
>> >>>   ----- Method: Browser>>defineClass:notifying: (in category 'class
>> >>> functions') -----
>> >>>   defineClass: defString notifying: aController
>> >>>         "The receiver's textual content is a request to define a new
>> >>> class. The
>> >>>         source code is defString. If any errors occur in compilation,
>> >>> notify
>> >>>         aController."
>> >>>         | oldClass class newClassName defTokens keywdIx envt |
>> >>>         oldClass := self selectedClassOrMetaClass.
>> >>>         defTokens := defString findTokens: Character separators.
>> >>>
>> >>>         ((defTokens first = 'Trait' and: [defTokens second =
>> >>> 'named:'])
>> >>>                 or: [defTokens second = 'classTrait'])
>> >>>                 ifTrue: [^self defineTrait: defString notifying:
>> >>> aController].
>> >>>
>> >>>         keywdIx := defTokens findFirst: [:x | x beginsWith:
>> >>> 'category'].
>> >>>         envt := self selectedEnvironment.
>> >>>         keywdIx := defTokens findFirst: [:x | '*subclass*' match: x].
>> >>>         newClassName := (defTokens at: keywdIx+1) copyWithoutAll:
>> >>> '#()'.
>> >>>         ((oldClass isNil or: [oldClass theNonMetaClass name asString
>> >>> ~=
>> >>> newClassName])
>> >>>                 and: [envt includesKey: newClassName asSymbol])
>> >>> ifTrue:
>> >>>                         ["Attempting to define new class over existing
>> >>> one
>> >>> when
>> >>>                                 not looking at the original one in
>> >>> this
>> >>> browser..."
>> >>>                         (self confirm: ((newClassName , ' is an
>> >>> existing
>> >>> class in this system.
>> >>>   Redefining it might cause serious problems.
>> >>>   Is this really what you want to do?') asText makeBoldFrom: 1 to:
>> >>> newClassName size))
>> >>>                                 ifFalse: [^ false]].
>> >>>         "ar 8/29/1999: Use oldClass superclass for defining oldClass
>> >>>         since oldClass superclass knows the definerClass of oldClass."
>> >>>         oldClass ifNotNil:[oldClass := oldClass superclass].
>> >>>         class := envt beCurrentDuring:
>> >>>                 [oldClass subclassDefinerClass
>> >>>                                 evaluate: defString
>> >>>                                 in: envt
>> >>>                                 notifying: aController
>> >>>                                 logged: false].
>> >>>         (class isKindOf: Behavior)
>> >>> +               ifTrue: [self changed: #systemCategoryList; changed:
>> >>> #classList.
>> >>> +                               self clearUserEditFlag;
>> >>> spawnOrNavigateTo:
>> >>> class.
>> >>> -               ifTrue: [self changed: #systemCategoryList.
>> >>> -                               self changed: #classList.
>> >>> -                               self clearUserEditFlag.
>> >>> -                               self setClass: class selector: nil.
>> >>> -                               "self clearUserEditFlag; editClass."
>> >>>                                 ^ true]
>> >>>                 ifFalse: [^ false]!
>> >>>
>> >>> Item was added:
>> >>> + ----- Method: Browser>>spawnOrNavigateTo: (in category 'private')
>> >>> -----
>> >>> + spawnOrNavigateTo: aClass
>> >>> +       self setClass: aClass selector: nil!
>> >>>
>> >>> Item was changed:
>> >>>   ----- Method: Debugger>>mainContextStackMenu: (in category 'context
>> >>> stack menu') -----
>> >>>   mainContextStackMenu: aMenu
>> >>>         "Set up the menu appropriately for the context-stack-list,
>> >>> unshifted"
>> >>>         <contextStackMenuShifted: false>
>> >>>         ^ 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)
>> >>>                         -
>> >>>                         ('references    (r)'
>> >>> browseVariableReferences)
>> >>>                         ('assignments    (a)'
>> >>> browseVariableAssignments)
>> >>>                         -
>> >>>                         ('class refs (N)'
>> >>> browseClassRefs)
>> >>>                         ('browse full (b)'
>> >>> browseMethodFull)
>> >>>                         ('file out '
>> >>> fileOutMessage)
>> >>>                         -
>> >>> +                       ('copy bug report to clipboard'
>> >>> copyBugReportToClipboard));
>> >>> -                       ('mail out bug report'
>> >>> mailOutBugReport)
>> >>> -                       ('bug report to clipboard'
>> >>> copyBugReportToClipboard));
>> >>>                 yourself
>> >>>   !
>> >>>
>> >>> Item was changed:
>> >>>   ----- Method: HierarchyBrowser>>setClass: (in category
>> >>> 'initialization')
>> >>> -----
>> >>> + setClass: aClass
>> >>> +       self initHierarchyForClass: (centralClass ifNil: [ aClass ]).
>> >>> +       super setClass: aClass!
>> >>> - setClass: aClass
>> >>> -
>> >>> -       self initHierarchyForClass: aClass.
>> >>> -       super setClass: aClass.!
>> >>>
>> >>> Item was added:
>> >>> + ----- Method: HierarchyBrowser>>spawnOrNavigateTo: (in category
>> >>> 'private') -----
>> >>> + spawnOrNavigateTo: aClass
>> >>> +       (aClass inheritsFrom: centralClass)
>> >>> +               ifTrue: [ super spawnOrNavigateTo: aClass ]
>> >>> +               ifFalse: [ self systemNavigation browseHierarchy:
>> >>> aClass
>> >>> ]!
>> >>>
>> >>> Item was changed:
>> >>>   ----- Method: HierarchyBrowser>>updateAfterClassChange (in category
>> >>> 'initialization') -----
>> >>>   updateAfterClassChange
>> >>>         "It is possible that some the classes comprising the hierarchy
>> >>> have changed, so reinitialize the entire browser."
>> >>>
>> >>> +       | priorSelection |
>> >>> +       priorSelection := self selectedClassName.
>> >>> +
>> >>>         (centralClass notNil and: [centralClass isObsolete not])
>> >>> +               ifTrue: [self initHierarchyForClass: centralClass].
>> >>> +
>> >>> +       (self classListIndexOf: priorSelection) > 0
>> >>> +               ifTrue: [self selectClassNamed: priorSelection].!
>> >>> -               ifTrue: [self initHierarchyForClass: centralClass]!
>> >>>
>> >>>
>> >>
>> >>
>> >>
>> >> --
>> >> _,,,^..^,,,_
>> >> best, Eliot
>> >>
>> >>
>> >>
>>
>
>
>
> --
> _,,,^..^,,,_
> best, Eliot
>
>
>