<html>
<head>
<meta http-equiv="Content-Type" content="text/html; charset=iso-8859-1">
<meta name="Generator" content="Microsoft Exchange Server">
<!-- converted from text --><style><!-- .EmailQuote { margin-left: 1pt; padding-left: 4pt; border-left: #800000 2px solid; } --></style>
</head>
<body>
<meta content="text/html; charset=UTF-8">
<style type="text/css" style="">
<!--
p
        {margin-top:0;
        margin-bottom:0}
-->
</style>
<div dir="ltr">
<div id="x_divtagdefaultwrapper" dir="ltr" style="font-size:12pt; color:#000000; font-family:Calibri,Helvetica,sans-serif">
<p>Hi Nicolas, thanks for your submission! :-)</p>
<p><br>
</p>
<p>I took a short look at it. It's definitively an improvement compared to the state of the art!</p>
<p>Actually, TBH I think that my proposal enables us to get completely rid of all the hard-coded indices stuff, whereas you collate this stuff a bit only. In contrast, an InspectorField will free us completely from that mess.</p>
<p>I definitively like the idea of #<span>extraInspectorFields! This way we can extend the inspector for a certain class without subclassing Inspector at all.</span></p>
<p><span><br>
</span></p>
<p>However, both approaches have merging conflicts. Personally, I would suggest getting the InspectorField quickly reviewed and merging it into Trunk. After that, we could rewrite your approach of #extraInspectorFields to make it use InspectorField.</p>
<p>(Please do not misunderstand me: I absolutely value your work and motivation to improve the inspector. I wish we can combine the best of our both approaches. And, to make it even more complicated, Chris mentioned some enhancements he wrote for the inspector
 fields in past, too ...)</p>
<p><br>
</p>
<p>Happy Squeak! :-)</p>
<p>Best,</p>
<p>Christoph</p>
<div id="x_Signature">
<div id="x_divtagdefaultwrapper" dir="ltr" style="font-size:12pt; color:rgb(0,0,0); font-family:Calibri,Helvetica,sans-serif,EmojiFont,"Apple Color Emoji","Segoe UI Emoji",NotoColorEmoji,"Segoe UI Symbol","Android Emoji",EmojiSymbols">
<div name="x_divtagdefaultwrapper" style="font-family:Calibri,Arial,Helvetica,sans-serif; font-size:; margin:0">
<div><font size="2" color="#808080"></font></div>
</div>
</div>
</div>
</div>
<hr tabindex="-1" style="display:inline-block; width:98%">
<div id="x_divRplyFwdMsg" dir="ltr"><font face="Calibri, sans-serif" color="#000000" style="font-size:11pt"><b>Von:</b> Squeak-dev <squeak-dev-bounces@lists.squeakfoundation.org> im Auftrag von commits@source.squeak.org <commits@source.squeak.org><br>
<b>Gesendet:</b> Freitag, 6. März 2020 00:13:35<br>
<b>An:</b> squeak-dev@lists.squeakfoundation.org<br>
<b>Betreff:</b> [squeak-dev] The Inbox: Tools-nice.956.mcz</font>
<div> </div>
</div>
</div>
<font size="2"><span style="font-size:10pt;">
<div class="PlainText">Nicolas Cellier uploaded a new version of Tools to project The Inbox:<br>
<a href="http://source.squeak.org/inbox/Tools-nice.956.mcz">http://source.squeak.org/inbox/Tools-nice.956.mcz</a><br>
<br>
==================== Summary ====================<br>
<br>
Name: Tools-nice.956<br>
Author: nice<br>
Time: 6 March 2020, 12:13:33.047985 am<br>
UUID: 68a4728a-05bb-4255-ba4a-211be07f2d24<br>
Ancestors: Tools-mt.955<br>
<br>
My own superficial refactoring of Inspector (June 2019), probably less deep than ct.<br>
<br>
Consider that the field list is decomposed into<br>
- fixedFields<br>
- variableFields<br>
<br>
The fixedFields include<br>
- baseFields: self, all inst var, the instance variables<br>
- extraFields: these are fields to be performed (message selectors) - ask object class for #extraInspectorFields<br>
<br>
The variableFields are the keys (index)  for collections, or can be composite for a Context<br>
<br>
With those simple rules, selection index handling is still a bit convoluted. But we have enough genericity so as to encapsulate uggliness in superclass, and let the subclasses concentrate on the contents.<br>
<br>
=============== Diff against Tools-mt.955 ===============<br>
<br>
Item was removed:<br>
- ----- Method: ContextInspector>>fieldList (in category 'accessing') -----<br>
- fieldList<br>
-        "Answer the base field list plus an abbreviated list of indices."<br>
-        | tempNames stackIndices |<br>
-        tempNames := object tempNames collect:[:t| '[',t,']'].<br>
-        stackIndices := (object numTemps + 1 to: object stackPtr) collect: [:i| i printString].<br>
-        ^self baseFieldList, tempNames, stackIndices!<br>
<br>
Item was removed:<br>
- ----- Method: ContextInspector>>selection (in category 'accessing') -----<br>
- selection<br>
-        "The receiver has a list of variables of its inspected object.<br>
-        One of these is selected. Answer the value of the selected variable."<br>
-        | basicIndex |<br>
-        selectionIndex = 0 ifTrue: [^ ''].<br>
-        selectionIndex = 1 ifTrue: [^ object].<br>
-        selectionIndex = 2 ifTrue: [^ object longPrintStringLimitedTo: 20000].<br>
-        selectionIndex - 2 <= object class instSize ifTrue:<br>
-                [^object instVarAt: selectionIndex - 2].<br>
-        basicIndex := selectionIndex - 2 - object class instSize.<br>
-        basicIndex <= object numTemps ifTrue:<br>
-                [^object debuggerMap namedTempAt: basicIndex in: object].<br>
-        basicIndex <= object stackPtr ifTrue:<br>
-                [^object at: basicIndex].<br>
-        ^nil<br>
- !<br>
<br>
Item was added:<br>
+ ----- Method: ContextInspector>>variableFieldList (in category 'accessing') -----<br>
+ variableFieldList<br>
+        "Separate the temps from the rest of the stack"<br>
+        | tempNames stackIndices |<br>
+        tempNames := object tempNames collect:[:t| '[',t,']'].<br>
+        stackIndices := (object numTemps + 1 to: object stackPtr) collect: [:i| i printString].<br>
+        ^tempNames, stackIndices!<br>
<br>
Item was added:<br>
+ ----- Method: ContextInspector>>variableFieldSelection: (in category 'accessing') -----<br>
+ variableFieldSelection: rank<br>
+        rank <= object numTemps ifTrue:<br>
+                [^object debuggerMap namedTempAt: rank in: object].<br>
+        rank <= object stackPtr ifTrue:<br>
+                [^object at: rank].<br>
+        ^nil<br>
+ !<br>
<br>
Item was removed:<br>
- ----- Method: DictionaryInspector>>fieldList (in category 'accessing') -----<br>
- fieldList<br>
-        ^ self baseFieldList<br>
-                , (keyArray collect: [:key | key printString])!<br>
<br>
Item was removed:<br>
- ----- Method: DictionaryInspector>>numberOfFixedFields (in category 'private') -----<br>
- numberOfFixedFields<br>
-        ^ 2 + object class instSize!<br>
<br>
Item was removed:<br>
- ----- Method: DictionaryInspector>>selection (in category 'selecting') -----<br>
- selection<br>
- <br>
-        selectionIndex <= (self numberOfFixedFields) ifTrue: [^ super selection].<br>
-        ^ object at: (keyArray at: selectionIndex - self numberOfFixedFields) ifAbsent:[nil]!<br>
<br>
Item was added:<br>
+ ----- Method: DictionaryInspector>>variableFieldList (in category 'accessing') -----<br>
+ variableFieldList<br>
+        ^ keyArray collect: [:key | key printString]!<br>
<br>
Item was added:<br>
+ ----- Method: DictionaryInspector>>variableFieldSelection: (in category 'selecting') -----<br>
+ variableFieldSelection: rank<br>
+        ^ object at: (keyArray at: rank) ifAbsent:[nil]!<br>
<br>
Item was added:<br>
+ ----- Method: Float>>extraInspectorFields (in category '*Tools-Inspector') -----<br>
+ extraInspectorFields<br>
+        ^super extraInspectorFields , #(signBit exponent significand successor predecessor)!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>baseFieldList (in category 'accessing') -----<br>
  baseFieldList<br>
         "Answer an Array consisting of 'self'<br>
         and the instance variable names of the inspected object."<br>
  <br>
         ^ (Array with: 'self' with: 'all inst vars')<br>
                         , object class allInstVarNames!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>copyName (in category 'menu commands') -----<br>
  copyName<br>
         "Copy the name of the current variable, so the user can paste it into the
<br>
         window below and work with is. If collection, do (xxx at: 1)."<br>
         | sel aClass variableNames |<br>
+        selectionIndex <= 2<br>
-        self selectionUnmodifiable<br>
                 ifTrue: [^ self changed: #flash].<br>
         aClass := self object class.<br>
         variableNames := aClass allInstVarNames.<br>
+        (aClass isVariable and: [selectionIndex > self numberOfFixedFields])<br>
-        (aClass isVariable and: [selectionIndex > (variableNames size + 2)])<br>
                 ifTrue: [sel := '(self basicAt: ' , (selectionIndex - (variableNames size + 2)) asString , ')']<br>
+                ifFalse: [selectionIndex - 2 <= variableNames size<br>
+                        ifTrue: [sel := variableNames at: selectionIndex - 2]<br>
+                        ifFalse: [sel := '(self ' , (self fieldList at: selectionIndex) , ')']].<br>
-                ifFalse: [sel := variableNames at: selectionIndex - 2].<br>
         (self selection isKindOf: Collection)<br>
                 ifTrue: [sel := '(' , sel , ' at: 1)'].<br>
         Clipboard clipboardText: sel asText!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>defsOfSelection (in category 'menu commands') -----<br>
  defsOfSelection<br>
         "Open a browser on all defining references to the selected instance variable, if that's what currently selected. "<br>
+        | sel |<br>
+        self hasAnInstanceVariableSelected ifFalse: [^ self changed: #flash].<br>
+        sel := object class allInstVarNames at: self selectionIndex - 2.<br>
+        self systemNavigation browseAllStoresInto: sel from: object class!<br>
-        | aClass sel |<br>
- <br>
-        self selectionUnmodifiable ifTrue: [^ self changed: #flash].<br>
-        (aClass := self object class) isVariable ifTrue: [^ self changed: #flash].<br>
- <br>
-        sel := aClass allInstVarNames at: self selectionIndex - 2.<br>
-        self systemNavigation  browseAllStoresInto: sel from: aClass!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>extraFieldList (in category 'accessing') -----<br>
+ extraFieldList<br>
+        "Answer an Array of optional messages to be sent to object."<br>
+ <br>
+        ^ (object respondsTo: #extraInspectorFields)<br>
+                ifTrue: [object extraInspectorFields]<br>
+                ifFalse: [Array empty]!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>fieldList (in category 'accessing') -----<br>
  fieldList<br>
         "Answer the base field list plus an abbreviated list of indices."<br>
  <br>
+        ^ self fixedFieldList , self variableFieldList!<br>
-        object class isVariable ifFalse: [^ self baseFieldList].<br>
-        ^ self baseFieldList ,<br>
-                (object basicSize <= (self i1 + self i2)<br>
-                        ifTrue: [(1 to: object basicSize)<br>
-                                                collect: [:i | i printString]]<br>
-                        ifFalse: [(1 to: self i1) , (object basicSize-(self i2-1) to: object basicSize)<br>
-                                                collect: [:i | i printString]])!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>fixedFieldList (in category 'accessing') -----<br>
+ fixedFieldList<br>
+        "Answer an Array consisting of all the fixed fields, including extra."<br>
+ <br>
+        ^ self baseFieldList , self extraFieldList!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>fixedFieldSelection (in category 'selecting') -----<br>
+ fixedFieldSelection<br>
+        "Selection when the selectionIndex is inside the fixedFieldList"<br>
+        selectionIndex = 0 ifTrue: [^ ''].<br>
+        selectionIndex = 1 ifTrue: [^ object].<br>
+        selectionIndex = 2 ifTrue: [^ object longPrintStringLimitedTo: 20000].<br>
+        (selectionIndex - 2) <= object class instSize<br>
+                ifTrue: [^ object instVarAt: selectionIndex - 2].<br>
+        ^object perform: (self fieldList at: selectionIndex)!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>hasAnInstanceVariableSelected (in category 'selecting') -----<br>
+ hasAnInstanceVariableSelected<br>
+        ^selectionIndex between: 3 and: 2 + object class instSize!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>numberOfFixedFields (in category 'accessing') -----<br>
+ numberOfFixedFields<br>
+        ^ 2 + object class instSize + self extraFieldList size!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>referencesToSelection (in category 'menu commands') -----<br>
  referencesToSelection<br>
+        "Open a browser on all references to the selected instance variable, if that's what currently selected."<br>
+        | sel |<br>
+        self hasAnInstanceVariableSelected ifFalse: [^ self changed: #flash].<br>
+        sel := object class allInstVarNames at: self selectionIndex - 2.<br>
+        self systemNavigation browseAllAccessesTo: sel from: object class!<br>
-        "Open a browser on all references to the selected instance variable, if that's what currently selected.  1/25/96 sw"<br>
-        | aClass sel |<br>
- <br>
-        self selectionUnmodifiable ifTrue: [^ self changed: #flash].<br>
-        (aClass := self object class) isVariable ifTrue: [^ self changed: #flash].<br>
- <br>
-        sel := aClass allInstVarNames at: self selectionIndex - 2.<br>
-        self systemNavigation   browseAllAccessesTo: sel from: aClass!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>replaceSelectionValue: (in category 'selecting') -----<br>
  replaceSelectionValue: anObject <br>
         "The receiver has a list of variables of its inspected object. One of these
<br>
         is selected. The value of the selected variable is set to the value, <br>
         anObject."<br>
         | basicIndex si instVarIndex |<br>
         selectionIndex <= 2 ifTrue: [<br>
                 self toggleIndex: (si := selectionIndex).  <br>
                 self toggleIndex: si.<br>
                 ^ object].<br>
         instVarIndex := selectionIndex - 2.<br>
         instVarIndex > object class instSize<br>
                 ifFalse: [^ object instVarAt: instVarIndex put: anObject].<br>
+        basicIndex := selectionIndex - self numberOfFixedFields.<br>
+        (object class isVariable and: [basicIndex between: 1 and: object basicSize])<br>
+                ifTrue: [self error: 'Cannot replace selection'].<br>
-        object class isVariable or: [self error: 'Cannot replace selection'].<br>
-        basicIndex := selectionIndex - 2 - object class instSize.<br>
         (object basicSize <= (self i1 + self i2)  or: [basicIndex <= self i1])<br>
                 ifTrue: [^object basicAt: basicIndex put: anObject]<br>
                 ifFalse: [^object basicAt: object basicSize - (self i1 + self i2) + basicIndex<br>
                                         put: anObject]!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>selection (in category 'selecting') -----<br>
  selection<br>
         "The receiver has a list of variables of its inspected object.<br>
         One of these is selected. Answer the value of the selected variable."<br>
+        | index |<br>
+        index := selectionIndex - self numberOfFixedFields.<br>
+        index <= 0<br>
+                ifTrue: [^self fixedFieldSelection] <br>
+                ifFalse: [^self variableFieldSelection: index] !<br>
-        | basicIndex |<br>
-        selectionIndex = 0 ifTrue: [^ ''].<br>
-        selectionIndex = 1 ifTrue: [^ object].<br>
-        selectionIndex = 2 ifTrue: [^ object longPrintStringLimitedTo: 20000].<br>
-        (selectionIndex - 2) <= object class instSize<br>
-                ifTrue: [^ object instVarAt: selectionIndex - 2].<br>
-        basicIndex := selectionIndex - 2 - object class instSize.<br>
-        (object basicSize <= (self i1 + self i2)  or: [basicIndex <= self i1])<br>
-                ifTrue: [^ object basicAt: basicIndex]<br>
-                ifFalse: [^ object basicAt: object basicSize - (self i1 + self i2) + basicIndex]!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>selectionUnmodifiable (in category 'selecting') -----<br>
  selectionUnmodifiable<br>
         "Answer if the current selected variable is modifiable via acceptance in the code pane.  For most inspectors, no selection and a selection of 'self' (selectionIndex = 1) and 'all inst vars' (selectionIndex = 2) are unmodifiable"<br>
  <br>
+        ^ selectionIndex <= 2 or: [selectionIndex between: 3 + object class instSize and: self numberOfFixedFields]!<br>
-        ^ selectionIndex <= 2!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>variableFieldList (in category 'accessing') -----<br>
+ variableFieldList<br>
+        "Answer an abbreviated list of indices for variable classes."<br>
+ <br>
+        object class isVariable ifFalse: [^Array empty].<br>
+        ^(object basicSize <= (self i1 + self i2)<br>
+                        ifTrue: [(1 to: object basicSize)<br>
+                                                collect: [:i | i printString]]<br>
+                        ifFalse: [(1 to: self i1) , (object basicSize-(self i2-1) to: object basicSize)<br>
+                                                collect: [:i | i printString]])!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>variableFieldSelection: (in category 'selecting') -----<br>
+ variableFieldSelection: rank<br>
+        "The receiver has a list of variables fields<br>
+        Answer the variable field at given rank."<br>
+        (object basicSize <= (self i1 + self i2)  or: [rank <= self i1])<br>
+                ifTrue: [^ object basicAt: rank]<br>
+                ifFalse: [^ object basicAt: object basicSize - (self i1 + self i2) + rank]!<br>
<br>
Item was added:<br>
+ ----- Method: Integer>>extraInspectorFields (in category '*Tools-inspector') -----<br>
+ extraInspectorFields<br>
+        ^super extraInspectorFields , #(hex highBitOfMagnitude)!<br>
<br>
Item was added:<br>
+ ----- Method: Object>>extraInspectorFields (in category '*Tools-inspecting') -----<br>
+ extraInspectorFields<br>
+        "Answer a list of fields to be performed for inspectors"<br>
+        ^#(identityHash)!<br>
<br>
Item was removed:<br>
- ----- Method: OrderedCollectionInspector>>fieldList (in category 'accessing') -----<br>
- fieldList<br>
-        object ifNil: [ ^ OrderedCollection new].<br>
-        ^ self baseFieldList ,<br>
-                (self objectSize <= (self i1 + self i2)<br>
-                        ifTrue: [(1 to: self objectSize)<br>
-                                                collect: [:i | i printString]]<br>
-                        ifFalse: [(1 to: self i1) , (self objectSize - (self i2-1) to: self objectSize)<br>
-                                                collect: [:i | i printString]])<br>
- "<br>
- OrderedCollection new inspect<br>
- (OrderedCollection newFrom: #(3 5 7 123)) inspect<br>
- (OrderedCollection newFrom: (1 to: 1000)) inspect<br>
- "!<br>
<br>
Item was added:<br>
+ ----- Method: OrderedCollectionInspector>>removeSelection (in category 'menu commands') -----<br>
+ removeSelection<br>
+        selectionIndex <= self numberOfFixedFields ifTrue: [^ self changed: #flash].<br>
+        object removeAt: self selectedObjectIndex.<br>
+        selectionIndex := 0.<br>
+        contents := ''.<br>
+        self changed: #inspectObject.<br>
+        self changed: #fieldList.<br>
+        self changed: #selection.<br>
+        self changed: #selectionIndex.!<br>
<br>
Item was changed:<br>
  ----- Method: OrderedCollectionInspector>>replaceSelectionValue: (in category 'selecting') -----<br>
  replaceSelectionValue: anObject <br>
         "The receiver has a list of variables of its inspected object. One of these
<br>
         is selected. The value of the selected variable is set to the value, anObject."<br>
  <br>
+        selectionIndex <= self numberOfFixedFields<br>
-        (selectionIndex - 2) <= object class instSize<br>
                 ifTrue: [^ super replaceSelectionValue: anObject].<br>
         object at: self selectedObjectIndex put: anObject!<br>
<br>
Item was changed:<br>
  ----- Method: OrderedCollectionInspector>>selectedObjectIndex (in category 'selecting') -----<br>
  selectedObjectIndex<br>
         "Answer the index of the inspectee's collection that the current selection refers to."<br>
  <br>
         | basicIndex |<br>
+        basicIndex := selectionIndex - self numberOfFixedFields.<br>
+        ^ (self objectSize <= (self i1 + self i2)  or: [basicIndex <= self i1])<br>
-        basicIndex := selectionIndex - 2 - object class instSize.<br>
-        ^ (object size <= (self i1 + self i2)  or: [basicIndex <= self i1])<br>
                 ifTrue: [basicIndex]<br>
+                ifFalse: [self objectSize - (self i1 + self i2) + basicIndex]!<br>
-                ifFalse: [object size - (self i1 + self i2) + basicIndex]!<br>
<br>
Item was removed:<br>
- ----- Method: OrderedCollectionInspector>>selection (in category 'selecting') -----<br>
- selection<br>
-        "The receiver has a list of variables of its inspected object.<br>
-        One of these is selected. Answer the value of the selected variable."<br>
- <br>
-        (selectionIndex - 2) <= object class instSize<br>
-                ifTrue: [^ super selection].<br>
-        ^ object at: self selectedObjectIndex!<br>
<br>
Item was added:<br>
+ ----- Method: OrderedCollectionInspector>>variableFieldList (in category 'accessing') -----<br>
+ variableFieldList<br>
+        object ifNil: [ ^ OrderedCollection new].<br>
+        ^(self objectSize <= (self i1 + self i2)<br>
+                        ifTrue: [(1 to: self objectSize)<br>
+                                                collect: [:i | i printString]]<br>
+                        ifFalse: [(1 to: self i1) , (self objectSize - (self i2-1) to: self objectSize)<br>
+                                                collect: [:i | i printString]])<br>
+ "<br>
+ OrderedCollection new inspect<br>
+ (OrderedCollection newFrom: #(3 5 7 123)) inspect<br>
+ (OrderedCollection newFrom: (1 to: 1000)) inspect<br>
+ "!<br>
<br>
Item was added:<br>
+ ----- Method: OrderedCollectionInspector>>variableFieldSelection: (in category 'selecting') -----<br>
+ variableFieldSelection: rank<br>
+        "The receiver has a list of variables of its inspected object.<br>
+        One of these is selected. Answer the value of the selected variable."<br>
+        <br>
+        | index |<br>
+        index := (object size <= (self i1 + self i2)  or: [rank <= self i1])<br>
+                ifTrue: [rank]<br>
+                ifFalse: [object size - (self i1 + self i2) + rank].<br>
+        ^object at: index!<br>
<br>
Item was removed:<br>
- ----- Method: SetInspector>>fieldList (in category 'accessing') -----<br>
- fieldList<br>
-        object<br>
-                ifNil: [^ Set new].<br>
-        ^ self baseFieldList<br>
-                , (object array<br>
-                                withIndexCollect: [:each :i | each ifNotNil: [i printString]])<br>
-                  select: [:each | each notNil]!<br>
<br>
Item was changed:<br>
  ----- Method: SetInspector>>removeSelection (in category 'menu') -----<br>
  removeSelection<br>
+        selectionIndex <= self numberOfFixedFields ifTrue: [^ self changed: #flash].<br>
-        (selectionIndex <= object class instSize) ifTrue: [^ self changed: #flash].<br>
         object remove: self selection.<br>
         selectionIndex := 0.<br>
+        contents := ''.<br>
-        self setContents: ''.<br>
         self changed: #inspectObject.<br>
         self changed: #fieldList.<br>
         self changed: #selection.<br>
         self changed: #selectionIndex.!<br>
<br>
Item was removed:<br>
- ----- Method: SetInspector>>selection (in category 'selecting') -----<br>
- selection<br>
-        selectionIndex = 0 ifTrue: [^ ''].<br>
-        selectionIndex = 1 ifTrue: [^ object].<br>
-        selectionIndex = 2 ifTrue: [^ object longPrintString].<br>
-        (selectionIndex - 2) <= object class instSize<br>
-                ifTrue: [^ object instVarAt: selectionIndex - 2].<br>
- <br>
-        ^ object array at: self arrayIndexForSelection ifAbsent: [ String empty ]!<br>
<br>
Item was added:<br>
+ ----- Method: SetInspector>>variableFieldList (in category 'accessing') -----<br>
+ variableFieldList<br>
+        object ifNil: [^ Set new].<br>
+        ^ (object array<br>
+                                withIndexCollect: [:each :i | each ifNotNil: [i printString]])<br>
+                  select: [:each | each notNil]!<br>
<br>
Item was added:<br>
+ ----- Method: SetInspector>>variableFieldSelection: (in category 'selecting') -----<br>
+ variableFieldSelection: rank<br>
+        "Note: the index is decoded from selected field name, because I am un-ordered"<br>
+        ^ object array at: self arrayIndexForSelection ifAbsent: [ String empty ]!<br>
<br>
Item was removed:<br>
- ----- Method: WeakSetInspector>>fieldList (in category 'accessing') -----<br>
- fieldList<br>
-        | slotIndices |<br>
-        object ifNil: [^ Set new].<br>
-        <br>
-        "Implementation note: do not use objectArray withIndexCollect: as super<br>
-        because this might collect indices in a WeakArray, leading to constantly changing fieldList<br>
-        as explained at <a href="http://bugs.squeak.org/view.php?id=6812">http://bugs.squeak.org/view.php?id=6812</a>"<br>
-        <br>
-        slotIndices := (Array new: object size) writeStream.<br>
-        object array withIndexDo: [:each :i |<br>
-                (each notNil and: [each ~= flagObject]) ifTrue: [slotIndices nextPut: i printString]].<br>
-        <br>
-        ^ self baseFieldList<br>
-                , slotIndices contents!<br>
<br>
Item was added:<br>
+ ----- Method: WeakSetInspector>>variableFielsList (in category 'accessing') -----<br>
+ variableFielsList<br>
+        | slotIndices |<br>
+        object ifNil: [^ Set new].<br>
+        <br>
+        "Implementation note: do not use objectArray withIndexCollect: as super<br>
+        because this might collect indices in a WeakArray, leading to constantly changing fieldList<br>
+        as explained at <a href="http://bugs.squeak.org/view.php?id=6812">http://bugs.squeak.org/view.php?id=6812</a>"<br>
+        <br>
+        slotIndices := (Array new: object size) writeStream.<br>
+        object array withIndexDo: [:each :i |<br>
+                (each notNil and: [each ~= flagObject]) ifTrue: [slotIndices nextPut: i printString]].<br>
+        <br>
+        ^  slotIndices contents!<br>
<br>
<br>
</div>
</span></font>
</body>
</html>