<html>
<head>
<meta http-equiv="Content-Type" content="text/html; charset=us-ascii">
<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>Just another question - #chasePointers currently looks the following:</p>
<p><br>
</p>
<p><span style="font-family:Calibri,Helvetica,sans-serif,EmojiFont,"Apple Color Emoji","Segoe UI Emoji",NotoColorEmoji,"Segoe UI Symbol","Android Emoji",EmojiSymbols; font-size:16px; white-space:pre"></span>"..."<br>
</p>
<p></p>
<div><span style="white-space:pre"></span>(Smalltalk includesKey: #PointerFinder)</div>
<div><span style="white-space:pre"></span>ifTrue: [PointerFinder on: selected]</div>
<div><span style="white-space:pre"></span>ifFalse: [self inspectPointers]]</div>
<div><span style="white-space:pre"></span>ensure: [self object: saved]</div>
<br>
<p></p>
<p>Is this actually required, as PointerFinder is located in the same package as Inspector?</p>
<p><br>
</p>
<p>Best,</p>
<p>Christoph</p>
<div id="x_Signature">
<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>
<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> Mittwoch, 2. Oktober 2019 23:14:40<br>
<b>An:</b> squeak-dev@lists.squeakfoundation.org<br>
<b>Betreff:</b> [squeak-dev] The Inbox: Tools-ct.900.mcz</font>
<div> </div>
</div>
</div>
<font size="2"><span style="font-size:10pt;">
<div class="PlainText">A new version of Tools was added to project The Inbox:<br>
<a href="http://source.squeak.org/inbox/Tools-ct.900.mcz">http://source.squeak.org/inbox/Tools-ct.900.mcz</a><br>
<br>
==================== Summary ====================<br>
<br>
Name: Tools-ct.900<br>
Author: ct<br>
Time: 2 October 2019, 11:14:40.791682 pm<br>
UUID: 357fedaf-0521-1f47-b744-53cedfc995c4<br>
Ancestors: Tools-ul.899<br>
<br>
Miscellaneous improvements, bugfixes & refactoring (mainly cleanup/deduplication) for the Inspector classes<br>
<br>
Overall deduplication; refines interface for subclasses:<br>
- Bundles updating logic<br>
- Introduces #typeOfSelection instead of hard-coded, redundant index numbers<br>
- Fixes #copyName for subclasses by introducing #nameOfSelection<br>
- Introduces cached #slotSpecs to describe fieldList on a higher level and increase reuse<br>
- Decomposes field list menu creation and override methods: saves heavy duplication and allows for more situational menus (only show items)<br>
- Merges menu items "stores into" and "assignments..." such as "defs of selection" and "references..."<br>
- International support in menus<br>
- Adds some simple formatting for field list<br>
- Removes some deprecations (#trash, #classOfSelection)<br>
- Recategorization<br>
- Refines long field list truncation and displays an ellipsis<br>
- Replace #i1 and #i2 by some more expressive names<br>
- Makes #inspectElement work again<br>
- Pass requestor to compiler when acceping a value (to get inline syntax errors)<br>
- immediately update value pane after replacing selection value<br>
- bugfix: always reset styling when value pane is updated<br>
- bugfix: show printString error instead of opening a Debugger, when 'all inst vars' is selected and any inst var cannot be printed<br>
- bugfix: not all displayed field list menu shortcuts were supported<br>
- Registers more specific #inspectorClass for Context<br>
- Don't absorb too many errors in #defaultIntegerBase<br>
- Fixes some comments and typos<br>
<br>
Still to do:<br>
- Consider further deprecations as described in <a href="http://forum.world.st/Tools-Possible-deprecations-in-Inspector-td5103248.html">
http://forum.world.st/Tools-Possible-deprecations-in-Inspector-td5103248.html</a><br>
<br>
Please review!<br>
I apologize for the large commit, but most changes are rather strongly linked and I found it hard to decouple them, preserving topological order. If needed, this may be also considered a working commit and I will be happy to implement all your feedback in further
 commits* :-)<br>
<br>
* but not before October 14th, as I'm going to take a vacation ;)<br>
<br>
<br>
<br>
---<br>
<br>
For testing, here are some expressions you can inspect (just to save you some typing effort):<br>
<br>
Morph new.<br>
(1 to: 200) collect: [:i | i -> (i asWords)] as: Dictionary.<br>
(1 to: 200) collect: #asWords as: OrderedCollection.<br>
(1 to: 200) collect: #asWords as: Set.<br>
{ World. Morph. nil. thisContext } as: WeakSet.<br>
[:i :x | |p qqqqq| p := i // x. qqqqq := x \\ i. [self halt] fork. thisContext] value: 42 value: 17.<br>
Parser >> #messagePart:repeat:.<br>
<br>
---<br>
<br>
=============== Diff against Tools-ul.899 ===============<br>
<br>
Item was changed:<br>
  Inspector subclass: #BasicInspector<br>
         instanceVariableNames: ''<br>
         classVariableNames: ''<br>
         poolDictionaries: ''<br>
         category: 'Tools-Inspector'!<br>
+ <br>
+ !BasicInspector commentStamp: 'ct 9/26/2019 13:34' prior: 0!<br>
+ I am a Inspector that displays the instance variables of my inspectee only, but not any kind of special informations such as my sibling classes do.!<br>
<br>
Item was changed:<br>
+ ----- Method: CompiledMethodInspector>>contentsIsString (in category 'accessing - selection') -----<br>
- ----- Method: CompiledMethodInspector>>contentsIsString (in category 'selecting') -----<br>
  contentsIsString<br>
-        "Hacked so contents empty when deselected"<br>
  <br>
+        ^ super contentsIsString or: [#(byteCodes header) includes: self typeOfSelection]!<br>
-        ^ #(0 2 3) includes: selectionIndex!<br>
<br>
Item was added:<br>
+ ----- Method: CompiledMethodInspector>>createSlotSpecs (in category 'accessing') -----<br>
+ createSlotSpecs<br>
+ <br>
+        | keys |<br>
+        keys := super createSlotSpecs first: 1.<br>
+        keys<br>
+                at: '<i>all bytecodes</i>' asHtmlText put: #byteCodes;<br>
+                at: '<i>header</i>' asHtmlText put: #header.<br>
+        keys addAll: (<br>
+                (1 to: object numLiterals) collect: [:i | 'literal', i -> {#literal. i}]).<br>
+        keys addAll: (self truncateList: (<br>
+                (object initialPC to: object size) collect: [:pc | pc asString -> {#pc. pc}])).<br>
+        ^ keys!<br>
<br>
Item was removed:<br>
- ----- Method: CompiledMethodInspector>>fieldList (in category 'accessing') -----<br>
- fieldList<br>
- <br>
-        | keys |<br>
-        keys := OrderedCollection new.<br>
-        keys add: 'self'.<br>
-        keys add: 'all bytecodes'.<br>
-        keys add: 'header'.<br>
-        1 to: object numLiterals do: [ :i |<br>
-                keys add: 'literal', i printString ].<br>
-        object initialPC to: object size do: [ :i |<br>
-                keys add: i printString ].<br>
-        ^ keys asArray<br>
-        !<br>
<br>
Item was added:<br>
+ ----- Method: CompiledMethodInspector>>nameOfSelection (in category 'accessing - selection') -----<br>
+ nameOfSelection<br>
+ <br>
+        ^ self typeOfSelection<br>
+                caseOf: {<br>
+                        [#byteCodes] -> ['self symbolic'].<br>
+                        [#header] -> ['self headerDescription'].<br>
+                        [#literal] -> ['(self objectAt: {1})' format: {(self selectedIndexOf: #literal) + 1}].<br>
+                        [#pc] -> ['(self at: {1})' format: {object initialPC + self selectedObjectIndex - 2}] }<br>
+                otherwise: [super nameOfSelection]!<br>
<br>
Item was changed:<br>
+ ----- Method: CompiledMethodInspector>>selection (in category 'accessing - selection') -----<br>
- ----- Method: CompiledMethodInspector>>selection (in category 'selecting') -----<br>
  selection<br>
  <br>
+        ^ self typeOfSelection<br>
+                caseOf: {<br>
+                        [#byteCodes] -> [object symbolic].<br>
+                        [#header] -> [object headerDescription].<br>
+                        [#literal] -> [object objectAt: (self selectedIndexOf: #literal) + 1].<br>
+                        [#pc] -> [object at: (self selectedIndexOf: #pc)] }<br>
+                otherwise: [super selection]!<br>
-        | bytecodeIndex |<br>
-        selectionIndex = 0 ifTrue: [^ ''].<br>
-        selectionIndex = 1 ifTrue: [^ object ].<br>
-        selectionIndex = 2 ifTrue: [^ object symbolic].<br>
-        selectionIndex = 3 ifTrue: [^ object headerDescription].<br>
-        selectionIndex <= (object numLiterals + 3) <br>
-                ifTrue: [ ^ object objectAt: selectionIndex - 2 ].<br>
-        bytecodeIndex := selectionIndex - object numLiterals - 3.<br>
-        ^ object at: object initialPC + bytecodeIndex - 1!<br>
<br>
Item was added:<br>
+ ----- Method: CompiledMethodInspector>>selectionIsSpecial (in category 'accessing - selection') -----<br>
+ selectionIsSpecial<br>
+ <br>
+        ^ super selectionIsSpecial or: [<br>
+                #(byteCodes header) includes: self typeOfSelection]!<br>
<br>
Item was changed:<br>
+ ----- Method: CompiledMethodInspector>>selectionUnmodifiable (in category 'accessing - selection') -----<br>
- ----- Method: CompiledMethodInspector>>selectionUnmodifiable (in category 'selecting') -----<br>
  selectionUnmodifiable<br>
-        "Answer if the current selected variable is unmodifiable via acceptance in the code pane.  For most inspectors, no selection and a selection of self (selectionIndex = 1) are unmodifiable"<br>
  <br>
         ^ true!<br>
<br>
Item was added:<br>
+ ----- Method: Context>>inspectorClass (in category '*Tools-Inspector') -----<br>
+ inspectorClass<br>
+ <br>
+        ^ ContextInspector!<br>
<br>
Item was added:<br>
+ ----- Method: ContextInspector>>createSlotSpecs (in category 'accessing') -----<br>
+ createSlotSpecs<br>
+ <br>
+        | tempNames stackIndices |<br>
+        tempNames := object tempNames<br>
+                collectWithIndex: [:t :i | '[', t, ']' -> {#tempVar. i}].<br>
+        stackIndices := (object numTemps + 1 to: object stackPtr)<br>
+                collect: [:i | i printString -> {#field. i}].<br>
+        ^ self createBaseSlotSpecs, tempNames, stackIndices!<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 added:<br>
+ ----- Method: ContextInspector>>nameOfSelection (in category 'accessing - selection') -----<br>
+ nameOfSelection<br>
+ <br>
+        self typeOfSelection = #tempVar<br>
+                ifFalse: [^ super nameOfSelection].<br>
+        ^ '(self at: {1})' format: {self selectedIndexOf: #tempVar}<br>
+                !<br>
<br>
Item was changed:<br>
+ ----- Method: ContextInspector>>selection (in category 'accessing - selection') -----<br>
- ----- Method: ContextInspector>>selection (in category 'accessing') -----<br>
  selection<br>
+        "Answer the value of the selected slot."<br>
+        <br>
+        ^ self typeOfSelection<br>
+                caseOf: {<br>
+                        [#tempVar] -> [object debuggerMap<br>
+                                namedTempAt: (self selectedIndexOf: #tempVar)<br>
+                                in: object].<br>
+                        [#field] -> [object at: self selectedObjectIndex] }<br>
+                otherwise: [super 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 changed:<br>
  ----- Method: ContextVariablesInspector>>aboutToStyle:forMorph: (in category 'styling') -----<br>
  aboutToStyle: aStyler forMorph: aMorph<br>
  <br>
-        (super aboutToStyle: aStyler forMorph: aMorph)<br>
-                ifFalse: [^ false].<br>
         aStyler<br>
                 classOrMetaClass: self doItReceiver class;<br>
                 context: self doItContext.<br>
+        ^ super aboutToStyle: aStyler forMorph: aMorph!<br>
-        ^ true!<br>
<br>
Item was added:<br>
+ ----- Method: ContextVariablesInspector>>addCollectionItemsTo: (in category 'menu') -----<br>
+ addCollectionItemsTo: aMenu<br>
+ <br>
+        self typeOfSelection = #allTempVars<br>
+                ifTrue: [^ false].<br>
+        ^ super addCollectionItemsTo: aMenu!<br>
<br>
Item was added:<br>
+ ----- Method: ContextVariablesInspector>>addFieldItemsTo: (in category 'menu') -----<br>
+ addFieldItemsTo: aMenu<br>
+ <br>
+        self typeOfSelection = #allTempVars<br>
+                ifTrue: [^ false].<br>
+        ^ super addFieldItemsTo: aMenu!<br>
<br>
Item was changed:<br>
+ ----- Method: ContextVariablesInspector>>contentsIsString (in category 'accessing - selection') -----<br>
- ----- Method: ContextVariablesInspector>>contentsIsString (in category 'selecting') -----<br>
  contentsIsString<br>
-        "Hacked so contents empty when deselected and = long printString when item 3"<br>
  <br>
+        self typeOfSelection = #allTempVars<br>
+                ifTrue: [^ true].<br>
+        ^ super contentsIsString!<br>
-        ^ (selectionIndex = 3) | (selectionIndex = 0) |<br>
-                (selectionIndex = 2 and: [object actualStackSize = 0])!<br>
<br>
Item was added:<br>
+ ----- Method: ContextVariablesInspector>>createSlotSpecs (in category 'accessing') -----<br>
+ createSlotSpecs<br>
+        "Refer to the comment in Inspector|fieldList."<br>
+ <br>
+        object == nil ifTrue: [^ OrderedDictionary new].<br>
+        ^ fieldList ifNil: [ | styler |<br>
+                styler := SHTextStylerST80 new.<br>
+                styler context: object.<br>
+                fieldList := OrderedDictionary newFrom: {<br>
+                        (styler styledTextFor: 'thisContext' asText) -> #thisContext.<br>
+                        '<i>stack top</i>' asHtmlText -> #stackTop.<br>
+                        '<i>all temp vars</i>' asHtmlText -> #allTempVars }<br>
+                        , (object tempNames collectWithIndex: [:name :index |<br>
+                                (styler styledTextFor: name asText) -> {#tempVar. index}])]!<br>
<br>
Item was changed:<br>
+ ----- Method: ContextVariablesInspector>>defaultIntegerBase (in category 'accessing') -----<br>
- ----- Method: ContextVariablesInspector>>defaultIntegerBase (in category 'selecting') -----<br>
  defaultIntegerBase<br>
         "Answer the default base in which to print integers.<br>
          Defer to the class the code is compiled in."<br>
+        | methodClass |<br>
+        methodClass := object method methodClass.<br>
+        ^ (methodClass respondsTo: #defaultIntegerBaseInDebugger)<br>
+                ifTrue: [methodClass defaultIntegerBaseInDebugger]<br>
+                ifFalse: [^ super defaultIntegerBase]!<br>
-        ^[object method methodClass defaultIntegerBaseInDebugger]<br>
-                on: MessageNotUnderstood<br>
-                do: [:ex| 10]!<br>
<br>
Item was removed:<br>
- ----- Method: ContextVariablesInspector>>fieldList (in category 'accessing') -----<br>
- fieldList <br>
-        "Refer to the comment in Inspector|fieldList."<br>
- <br>
-        object == nil ifTrue: [^Array with: 'thisContext'].<br>
-        ^fieldList ifNil:[fieldList := (Array with: 'thisContext' with: 'stack top' with: 'all temp vars') , object tempNames]!<br>
<br>
Item was added:<br>
+ ----- Method: ContextVariablesInspector>>nameOfSelection (in category 'accessing - selection') -----<br>
+ nameOfSelection<br>
+ <br>
+        ^ self typeOfSelection<br>
+                caseOf: {<br>
+                        [#thisContext] -> ['thisContext arguments first'].<br>
+                        [#stackTop] -> ['thisContext arguments first top'].<br>
+                        [#tempVar] -> [(self slotSpecs atIndex: self selectionIndex) key] }<br>
+                otherwise: [<br>
+                        super nameOfSelection]!<br>
<br>
Item was changed:<br>
+ ----- Method: ContextVariablesInspector>>replaceSelectionValue: (in category 'code') -----<br>
- ----- Method: ContextVariablesInspector>>replaceSelectionValue: (in category 'selecting') -----<br>
  replaceSelectionValue: anObject <br>
         "Refer to the comment in Inspector|replaceSelectionValue:."<br>
  <br>
+        self typeOfSelection = #tempVar<br>
+                ifFalse: [^ super replaceSelectionValue: anObject].<br>
+        ^ object namedTempAt: (self selectedIndexOf: #tempVar) put: anObject!<br>
-        ^selectionIndex = 1<br>
-                ifTrue: [object]<br>
-                ifFalse: [object namedTempAt: selectionIndex - 3 put: anObject]!<br>
<br>
Item was changed:<br>
+ ----- Method: ContextVariablesInspector>>selection (in category 'accessing - selection') -----<br>
- ----- Method: ContextVariablesInspector>>selection (in category 'selecting') -----<br>
  selection <br>
         "Refer to the comment in Inspector|selection."<br>
+        ^ self typeOfSelection<br>
-        ^selectionIndex<br>
                 caseOf: {<br>
+                        [#thisContext] -> [object].<br>
+                        [#stackTop] -> [object actualStackSize > 0 ifTrue: [object top] ifFalse: ['']].<br>
+                        [#allTempVars] -> [self tempsAndValues].<br>
+                        [#tempVar] -> [object debuggerMap namedTempAt: (self selectedIndexOf: #tempVar) in: object] }<br>
+                otherwise: [<br>
+                        super selection]<br>
+                        !<br>
-                        [0] -> [''].<br>
-                        [1] -> [object].<br>
-                        [2] -> [object actualStackSize > 0 ifTrue: [object top] ifFalse: ['']].<br>
-                        [3] -> [self tempsAndValues] }<br>
-                otherwise:<br>
-                        [object debuggerMap namedTempAt: selectionIndex - 3 in: object]!<br>
<br>
Item was added:<br>
+ ----- Method: ContextVariablesInspector>>selectionIsSpecial (in category 'accessing - selection') -----<br>
+ selectionIsSpecial<br>
+ <br>
+        ^ super selectionIsSpecial or: [self typeOfSelection = #allTempVars]!<br>
<br>
Item was added:<br>
+ ----- Method: ContextVariablesInspector>>selectionUnmodifiable (in category 'accessing - selection') -----<br>
+ selectionUnmodifiable<br>
+ <br>
+        ^ self typeOfSelection ~= #tempVar!<br>
<br>
Item was changed:<br>
+ ----- Method: ContextVariablesInspector>>tempsAndValues (in category 'accessing') -----<br>
- ----- Method: ContextVariablesInspector>>tempsAndValues (in category 'selecting') -----<br>
  tempsAndValues<br>
         "Answer a string of the temporary variables and their current values"<br>
+        | debuggerMap integerClasses |<br>
-        | debuggerMap integerClasses aStream |<br>
-        aStream := WriteStream on: (String new: 100).<br>
         debuggerMap := object debuggerMap.<br>
         integerClasses := Integer allSubclasses.<br>
+        ^ Text streamContents: [:stream |<br>
         (debuggerMap tempNamesForContext: object) doWithIndex:<br>
                 [:title :index | | temp |<br>
+                stream withAttribute: TextEmphasis bold do: [ <br>
+                        stream nextPutAll: title; nextPut: $:; space; tab; tab].<br>
-                 aStream nextPutAll: title; nextPut: $:; space; tab.<br>
                  temp := debuggerMap namedTempAt: index in: object.<br>
                  (integerClasses identityIndexOf: (object objectClass: temp)) ~= 0<br>
+                        ifTrue: [temp storeOn: stream base: self defaultIntegerBase]<br>
+                        ifFalse: [object print: temp on: stream].<br>
+                 stream cr]]!<br>
-                        ifTrue: [temp storeOn: aStream base: self defaultIntegerBase]<br>
-                        ifFalse: [object print: temp on: aStream].<br>
-                 aStream cr].<br>
-        ^aStream contents!<br>
<br>
Item was changed:<br>
  ----- Method: Debugger>>contextStackIndex:oldContextWas: (in category 'private') -----<br>
  contextStackIndex: anInteger oldContextWas: oldContext <br>
         "Change the context stack index to anInteger, perhaps in response to user selection."<br>
  <br>
+        | isNewMethod |<br>
-        | isNewMethod selectedContextSlotName index |<br>
         contextStackIndex := anInteger.<br>
         anInteger = 0 ifTrue:<br>
                 [currentCompiledMethod := contents := nil.<br>
                  self changed: #contextStackIndex.<br>
                  self decorateButtons.<br>
                  self contentsChanged.<br>
                  contextVariablesInspector object: nil.<br>
                  receiverInspector object: self receiver.<br>
                  ^self].<br>
-        selectedContextSlotName := contextVariablesInspector selectedSlotName.<br>
         isNewMethod := oldContext == nil<br>
                                         or: [oldContext method ~~ (currentCompiledMethod := self selectedContext method)].<br>
         isNewMethod ifTrue:<br>
                 [contents := self selectedMessage.<br>
                  self contentsChanged.<br>
                  self pcRange].<br>
         self changed: #contextStackIndex.<br>
         self decorateButtons.<br>
         contextVariablesInspector object: self selectedContext.<br>
-        ((index := contextVariablesInspector fieldList indexOf: selectedContextSlotName) ~= 0<br>
-         and: [index ~= contextVariablesInspector selectionIndex]) ifTrue:<br>
-                [contextVariablesInspector toggleIndex: index].<br>
         receiverInspector object: self receiver.<br>
         isNewMethod ifFalse:<br>
                 [self changed: #contentsSelection]!<br>
<br>
Item was added:<br>
+ ----- Method: DictionaryInspector>>addCollectionItemsTo: (in category 'menu') -----<br>
+ addCollectionItemsTo: aMenu<br>
+ <br>
+        self typeOfSelection = #self ifFalse: [^ false].<br>
+        aMenu addTranslatedList: #(<br>
+                "-"<br>
+                ('refresh view'                         refreshView)<br>
+                ('add key'                                      addEntry)).!<br>
<br>
Item was changed:<br>
+ ----- Method: DictionaryInspector>>addEntry (in category 'menu commands') -----<br>
- ----- Method: DictionaryInspector>>addEntry (in category 'menu') -----<br>
  addEntry<br>
-        | newKey aKey |<br>
  <br>
+        | newKey |<br>
+        newKey := self requestKeyFor: '' onCancel: [^ self].<br>
+        self addEntry: newKey.!<br>
-        newKey := UIManager default request:<br>
- 'Enter new key, then type RETURN.<br>
- (Expression will be evaluated for value.)<br>
- Examples:  #Fred    ''a string''   3+4'.<br>
-        aKey := Compiler evaluate: newKey.<br>
-        object at: aKey put: nil.<br>
-        self calculateKeyArray.<br>
-        selectionIndex := self numberOfFixedFields + (keyArray indexOf: aKey).<br>
-        self changed: #inspectObject.<br>
-        self changed: #selectionIndex.<br>
-        self changed: #fieldList.<br>
-        self update!<br>
<br>
Item was changed:<br>
+ ----- Method: DictionaryInspector>>addEntry: (in category 'menu commands') -----<br>
- ----- Method: DictionaryInspector>>addEntry: (in category 'selecting') -----<br>
  addEntry: aKey<br>
+ <br>
         object at: aKey put: nil.<br>
         self calculateKeyArray.<br>
+        self selectKey: aKey.<br>
+        self updateEntries.!<br>
-        selectionIndex := self numberOfFixedFields + (keyArray indexOf: aKey).<br>
-        self changed: #inspectObject.<br>
-        self changed: #selectionIndex.<br>
-        self changed: #fieldList.<br>
-        self update!<br>
<br>
Item was added:<br>
+ ----- Method: DictionaryInspector>>addFieldItemsTo: (in category 'menu') -----<br>
+ addFieldItemsTo: aMenu<br>
+ <br>
+        (super addFieldItemsTo: aMenu)<br>
+                ifFalse: [^ false].<br>
+        self typeOfSelection = #field<br>
+                ifFalse: [^ false].<br>
+        self selectedKey isSymbol ifTrue: [<br>
+                aMenu addTranslatedList: #(<br>
+                        ('senders of this key'                  sendersOfSelectedKey))].<br>
+        aMenu addTranslatedList: #(<br>
+                ('inspect key'                          inspectKey)<br>
+                ('references'                           selectionReferences)<br>
+                ('rename key'                           renameEntry)<br>
+                ('remove key (x)'                       removeSelection)).<br>
+        ^ true!<br>
<br>
Item was changed:<br>
+ ----- Method: DictionaryInspector>>calculateKeyArray (in category 'private') -----<br>
- ----- Method: DictionaryInspector>>calculateKeyArray (in category 'selecting') -----<br>
  calculateKeyArray<br>
         "Recalculate the KeyArray from the object being inspected"<br>
  <br>
         keyArray := object keysSortedSafely asArray.<br>
         selectionIndex := 0.<br>
  !<br>
<br>
Item was removed:<br>
- ----- Method: DictionaryInspector>>contentsIsString (in category 'selecting') -----<br>
- contentsIsString<br>
-        "Hacked so contents empty when deselected"<br>
- <br>
-        ^ (selectionIndex = 0)!<br>
<br>
Item was removed:<br>
- ----- Method: DictionaryInspector>>copyName (in category 'menu') -----<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 |<br>
-        self selectionIndex <= self numberOfFixedFields<br>
-                ifTrue: [super copyName]<br>
-                ifFalse: [sel := String streamContents: [:strm | <br>
-                                                        strm nextPutAll: '(self at: '.<br>
-                                                        (keyArray at: selectionIndex - self numberOfFixedFields)<br>
-                                                                storeOn: strm.<br>
-                                                        strm nextPutAll: ')'].<br>
-                        Clipboard clipboardText: sel asText                      "no undo allowed"]!<br>
<br>
Item was added:<br>
+ ----- Method: DictionaryInspector>>createSlotSpecs (in category 'accessing') -----<br>
+ createSlotSpecs<br>
+ <br>
+        | keys |<br>
+        keys := super createSlotSpecs first: 2.<br>
+        keys addAll: (self truncateList: (<br>
+                keyArray withIndexCollect: [:key :index |<br>
+                        key printString -> {#field. key}])).<br>
+        ^ keys!<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 changed:<br>
  ----- Method: DictionaryInspector>>inspectKey (in category 'menu commands') -----<br>
  inspectKey<br>
         "Create and schedule an Inspector on the receiver's model's currently selected key."<br>
  <br>
+        self typeOfSelection = #field ifFalse: [^ self].<br>
+        self selectedKey inspect.!<br>
-        selectionIndex >= self numberOfFixedFields ifTrue:<br>
-                [(keyArray at: selectionIndex - self numberOfFixedFields) inspect]!<br>
<br>
Item was added:<br>
+ ----- Method: DictionaryInspector>>inspectorKey:from: (in category 'menu') -----<br>
+ inspectorKey: aChar from: view<br>
+ <br>
+        aChar = $x<br>
+                ifTrue: [self removeSelection]<br>
+                ifFalse: [^ super inspectorKey: aChar from: view].<br>
+        !<br>
<br>
Item was added:<br>
+ ----- Method: DictionaryInspector>>inspectorOverflowText (in category 'toolbuilder') -----<br>
+ inspectorOverflowText<br>
+ <br>
+        ^ ('<{1} elements at keys "{2}" to "{3}" not shown!!>' format: {<br>
+                self object size - self maximumIndicesSize.<br>
+                keyArray at: self maximumIndicesSize - self minimumLastIndicesSize.<br>
+                keyArray at: self object size - self minimumLastIndicesSize })<br>
+                        asText<br>
+                                addAttribute: TextEmphasis italic;<br>
+                                yourself!<br>
<br>
Item was removed:<br>
- ----- Method: DictionaryInspector>>mainFieldListMenu: (in category 'menu') -----<br>
- mainFieldListMenu: aMenu<br>
- <br>
-        ^ aMenu addList: #(     <br>
-                ('inspect'                                                      inspectSelection)<br>
-                ('inspect key'                                          inspectKey)<br>
-                ('copy name'                                            copyName)<br>
-                ('references'                                           selectionReferences)<br>
-                ('objects pointing to this value'               objectReferencesToSelection)<br>
-                ('senders of this key'                          sendersOfSelectedKey)<br>
-                -<br>
-                ('refresh view'                                         refreshView)<br>
-                ('add key'                                                      addEntry)<br>
-                ('rename key'                                           renameEntry)<br>
-                -<br>
-                ('remove'                                                       removeSelection)<br>
-                ('basic inspect'                                        inspectBasic));<br>
-        yourself<br>
- !<br>
<br>
Item was added:<br>
+ ----- Method: DictionaryInspector>>nameOfSelection (in category 'accessing - selection') -----<br>
+ nameOfSelection<br>
+ <br>
+        self typeOfSelection = #field<br>
+                ifFalse: [super nameOfSelection].<br>
+        ^ '(self at: {1})' format: {self selectedKey}!<br>
<br>
Item was changed:<br>
  ----- Method: DictionaryInspector>>numberOfFixedFields (in category 'private') -----<br>
  numberOfFixedFields<br>
+        self deprecated.<br>
+        ^ self variableListOffset!<br>
-        ^ 2 + object class instSize!<br>
<br>
Item was changed:<br>
+ ----- Method: DictionaryInspector>>refreshView (in category 'menu commands') -----<br>
- ----- Method: DictionaryInspector>>refreshView (in category 'selecting') -----<br>
  refreshView<br>
+ <br>
         | i |<br>
         i := selectionIndex.<br>
         self calculateKeyArray.<br>
         selectionIndex := i.<br>
+        self updateEntries.!<br>
-        self changed: #fieldList.<br>
-        self changed: #contents.!<br>
<br>
Item was changed:<br>
+ ----- Method: DictionaryInspector>>removeSelection (in category 'menu commands') -----<br>
- ----- Method: DictionaryInspector>>removeSelection (in category 'menu') -----<br>
  removeSelection<br>
+ <br>
+        self typeOfSelection = #field ifFalse: [^ self changed: #flash].<br>
+        object removeKey: self selectedKey.<br>
-        selectionIndex = 0 ifTrue: [^ self changed: #flash].<br>
-        object removeKey: (keyArray at: selectionIndex - self numberOfFixedFields).<br>
         selectionIndex := 0.<br>
+        self calculateKeyArray; updateEntries.!<br>
-        contents := ''.<br>
-        self calculateKeyArray.<br>
-        self changed: #inspectObject.<br>
-        self changed: #selectionIndex.<br>
-        self changed: #fieldList.<br>
-        self changed: #selection.!<br>
<br>
Item was changed:<br>
+ ----- Method: DictionaryInspector>>renameEntry (in category 'menu commands') -----<br>
- ----- Method: DictionaryInspector>>renameEntry (in category 'menu') -----<br>
  renameEntry<br>
-        | newKey aKey value |<br>
  <br>
+        | newKey |<br>
+        self typeOfSelection = #field ifFalse: [^ self flash].<br>
+        newKey := self requestKeyFor: self selectedKey printString onCancel: [^ self].<br>
+        ^ self renameEntry: newKey!<br>
-        value := object at: (keyArray at: selectionIndex - self numberOfFixedFields).<br>
-        newKey := UIManager default request: <br>
- 'Enter new key, then type RETURN.<br>
- (Expression will be evaluated for value.)<br>
- Examples:  #Fred    ''a string''   3+4'<br>
-                 initialAnswer: (keyArray at: selectionIndex - self numberOfFixedFields) printString.<br>
-        aKey := Compiler evaluate: newKey.<br>
-        object removeKey: (keyArray at: selectionIndex - self numberOfFixedFields).<br>
-        object at: aKey put: value.<br>
-        self calculateKeyArray.<br>
-        selectionIndex := self numberOfFixedFields + (keyArray indexOf: aKey).<br>
-        self changed: #selectionIndex.<br>
-        self changed: #inspectObject.<br>
-        self changed: #fieldList.<br>
-        self update!<br>
<br>
Item was added:<br>
+ ----- Method: DictionaryInspector>>renameEntry: (in category 'menu commands') -----<br>
+ renameEntry: aKey<br>
+ <br>
+        object<br>
+                at: aKey put: self selection;<br>
+                removeKey: self selectedKey.<br>
+        self calculateKeyArray; updateEntries.<br>
+        self selectKey: aKey.!<br>
<br>
Item was changed:<br>
+ ----- Method: DictionaryInspector>>replaceSelectionValue: (in category 'code') -----<br>
+ replaceSelectionValue: anObject<br>
+ <br>
+        self typeOfSelection = #field<br>
+                ifFalse: [^ super replaceSelectionValue: anObject].<br>
- ----- Method: DictionaryInspector>>replaceSelectionValue: (in category 'selecting') -----<br>
- replaceSelectionValue: anObject <br>
-        selectionIndex <= self numberOfFixedFields<br>
-                ifTrue: [^ super replaceSelectionValue: anObject].<br>
         ^ object<br>
+                at: (keyArray at: selectionIndex - self variableListOffset)<br>
-                at: (keyArray at: selectionIndex - self numberOfFixedFields)<br>
                 put: anObject!<br>
<br>
Item was added:<br>
+ ----- Method: DictionaryInspector>>requestKeyFor:onCancel: (in category 'menu commands') -----<br>
+ requestKeyFor: initialAnswer onCancel: aBlock<br>
+ <br>
+        | input |<br>
+        input := UIManager default request: <br>
+ 'Enter expression for new key.<br>
+ (Examples:  #Fred    ''a string''   3+4)'<br>
+                 initialAnswer: initialAnswer.<br>
+        input isEmptyOrNil ifTrue: [^ aBlock value].<br>
+        ^ Compiler evaluate: input!<br>
<br>
Item was added:<br>
+ ----- Method: DictionaryInspector>>selectKey: (in category 'accessing - selection') -----<br>
+ selectKey: aKey<br>
+ <br>
+        self selectionIndex: self variableListOffset + (keyArray indexOf: aKey).!<br>
<br>
Item was added:<br>
+ ----- Method: DictionaryInspector>>selectedKey (in category 'accessing - selection') -----<br>
+ selectedKey<br>
+ <br>
+        self typeOfSelection = #field ifFalse: [^ nil].<br>
+        ^ self selectedIndexOf: #field!<br>
<br>
Item was changed:<br>
+ ----- Method: DictionaryInspector>>selection (in category 'accessing - selection') -----<br>
- ----- Method: DictionaryInspector>>selection (in category 'selecting') -----<br>
  selection<br>
  <br>
+        self typeOfSelection = #field<br>
+                ifFalse: [^ super selection].<br>
+        ^ object at: self selectedKey!<br>
-        selectionIndex <= (self numberOfFixedFields) ifTrue: [^ super selection].<br>
-        ^ object at: (keyArray at: selectionIndex - self numberOfFixedFields) ifAbsent:[nil]!<br>
<br>
Item was changed:<br>
+ ----- Method: DictionaryInspector>>selectionReferences (in category 'menu commands') -----<br>
- ----- Method: DictionaryInspector>>selectionReferences (in category 'menu') -----<br>
  selectionReferences<br>
         "Create a browser on all references to the association of the current selection."<br>
  <br>
+        self flag: #ct "When does this work?".<br>
+        self typeOfSelection = #field ifFalse: [^ self changed: #flash].<br>
+        (object isMemberOf: MethodDictionary)<br>
+                ifTrue: [^ self changed: #flash]. "ct: why?"<br>
+        self systemNavigation browseAllCallsOn: (object associationAt: self selectedKey)!<br>
-        self selectionIndex <= self numberOfFixedFields ifTrue: [^ self changed: #flash].<br>
-        object class == MethodDictionary ifTrue: [^ self changed: #flash].<br>
-        self systemNavigation browseAllCallsOn: (object associationAt: (keyArray at: selectionIndex - self numberOfFixedFields))!<br>
<br>
Item was changed:<br>
+ ----- Method: DictionaryInspector>>sendersOfSelectedKey (in category 'menu commands') -----<br>
- ----- Method: DictionaryInspector>>sendersOfSelectedKey (in category 'menu') -----<br>
  sendersOfSelectedKey<br>
         "Create a browser on all senders of the selected key"<br>
+ <br>
         | aKey |<br>
+        ((aKey := self selectedKey) isSymbol)<br>
-        self selectionIndex = 0<br>
-                ifTrue: [^ self changed: #flash].<br>
-        ((aKey := keyArray at: selectionIndex  - self numberOfFixedFields) isSymbol)<br>
                 ifFalse: [^ self changed: #flash].<br>
         SystemNavigation default browseAllCallsOn: aKey!<br>
<br>
Item was added:<br>
+ ----- Method: DictionaryInspector>>variableListOffset (in category 'accessing') -----<br>
+ variableListOffset<br>
+ <br>
+        ^ 1!<br>
<br>
Item was changed:<br>
  StringHolder subclass: #Inspector<br>
+        instanceVariableNames: 'object selectionIndex timeOfLastListUpdate selectionUpdateTime context expression shouldStyleValuePane slotSpecs'<br>
-        instanceVariableNames: 'object selectionIndex timeOfLastListUpdate selectionUpdateTime context expression shouldStyleValuePane'<br>
         classVariableNames: ''<br>
         poolDictionaries: ''<br>
         category: 'Tools-Inspector'!<br>
  <br>
  !Inspector commentStamp: '<historical>' prior: 0!<br>
  I represent a query path into the internal representation of an object. As a StringHolder, the string I represent is the value of the currently selected variable of the observed object.!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>aboutToStyle:forMorph: (in category 'styling') -----<br>
  aboutToStyle: aStyler forMorph: aMorph<br>
  <br>
         (aMorph knownName = #valuePane and: [shouldStyleValuePane not])<br>
                 ifTrue: [^ false].<br>
         <br>
         aStyler <br>
+                classOrMetaClass: self object class;<br>
-                classOrMetaClass: object class;<br>
                 parseAMethod: false.<br>
+        ^ true!<br>
-        ^true!<br>
<br>
Item was removed:<br>
- ----- Method: Inspector>>accept: (in category 'selecting') -----<br>
- accept: aString <br>
-        | result |<br>
-        result := self doItReceiver class evaluatorClass new<br>
-                                evaluate: (ReadStream on: aString)<br>
-                                in: self doItContext<br>
-                                to: self doItReceiver<br>
-                                notifying: nil  "fix this"<br>
-                                ifFail: [self changed: #flash.<br>
-                                        ^ false].<br>
-        self replaceSelectionValue: result.<br>
-        self changed: #contents.<br>
-        ^ true!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>accept:notifying: (in category 'code') -----<br>
+ accept: aString notifying: aController<br>
+        | result |<br>
+        self selectionUnmodifiable ifTrue: [<br>
+                self inform: 'Selection is unmodifiable'.<br>
+                ^ false].<br>
+        result := self doItReceiver class evaluatorClass new<br>
+                evaluate: aString<br>
+                in: self doItContext<br>
+                to: self doItReceiver<br>
+                notifying: aController<br>
+                ifFail: [^ false].<br>
+        self<br>
+                replaceSelectionValue: result;<br>
+                update.<br>
+        ^ true!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>addClassItemsTo: (in category 'menu') -----<br>
+ addClassItemsTo: aMenu<br>
+ <br>
+        aMenu addTranslatedList: #(<br>
+                ('browse full (b)'                                              browseClass)<br>
+                ('browse hierarchy (h)'                         classHierarchy)<br>
+                ('browse protocol (p)'                          browseFullProtocol)).<br>
+        self typeOfSelection = #self ifFalse: [^ false].<br>
+        aMenu addTranslatedList: #(<br>
+                -<br>
+                ('references... (r)'                                            browseVariableReferences)<br>
+                ('assignments... (a)'                                   browseVariableAssignments)<br>
+                ('class refs (N)'                                                       browseClassRefs)).<br>
+        ^ true!<br>
<br>
Item was changed:<br>
+ ----- Method: Inspector>>addCollectionItemsTo: (in category 'menu') -----<br>
- ----- Method: Inspector>>addCollectionItemsTo: (in category 'menu commands') -----<br>
  addCollectionItemsTo: aMenu<br>
         "If the current selection is an appropriate collection, add items to aMenu that cater to that kind of selection"<br>
  <br>
+        | selection |<br>
+        self typeOfSelection = #allInstVars ifTrue: [^ false].<br>
+        selection := self selectionOrObject.<br>
+        ((selection isKindOf: SequenceableCollection) and: [selection notEmpty])<br>
+                ifTrue: [ aMenu addTranslatedList: #(<br>
+                        ('inspect element...'           inspectElement)) ].<br>
+        ((selection respondsTo: #inspectElement) and: [(selection isKindOf: Inspector) not])<br>
+                ifTrue: [ aMenu addTranslatedList: #(<br>
+                        ('inspect property...'          inspectMenu)) ].<br>
+        ^ true!<br>
-        | sel |<br>
-        ((((sel := self selection) isMemberOf: Array) or: [sel isMemberOf: OrderedCollection]) and:
<br>
-                [sel size > 0]) ifTrue: [<br>
-                        aMenu addList: #(<br>
-                                ('inspect element...'                                   inspectElement))].<br>
- <br>
-        (sel respondsTo: #inspectElement) ifTrue: [<br>
-                        aMenu addList: #(<br>
-                                ('inspect property...'                          inspectElement))].!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>addFieldItemsTo: (in category 'menu') -----<br>
+ addFieldItemsTo: aMenu<br>
+ <br>
+        ({nil. #self. #'...'} includes: self typeOfSelection)<br>
+                ifTrue: [^ false].<br>
+        aMenu addTranslatedList: #(<br>
+                ('copy name (c)'                        copyName)).<br>
+        ^ true!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>addInstVarItemsTo: (in category 'menu') -----<br>
+ addInstVarItemsTo: aMenu<br>
+ <br>
+        aMenu addTranslatedList: #(<br>
+                ('references... (r)'                    browseVariableReferences)<br>
+                ('assignments... (a)'           browseVariableAssignments)).<br>
+        ^ true!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>addMorphicItemsTo: (in category 'menu') -----<br>
+ addMorphicItemsTo: aMenu<br>
+ <br>
+        aMenu addTranslatedList: #(<br>
+                ('tile for this value    (t)'                    tearOffTile)<br>
+                ('viewer for this value (v)'            viewerForValue)).<br>
+        ^ true!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>addObjectItemsTo: (in category 'menu') -----<br>
+ addObjectItemsTo: aMenu<br>
+ <br>
+        self typeOfSelection = #'...' ifTrue: [^ false].<br>
+        aMenu addTranslatedList: {<br>
+                {'inspect (i)'.                 #inspectSelection}.<br>
+                {'explore (I)'.                 #exploreSelection}.<br>
+                {'basic inspect'.               #inspectBasic.          'Inspect all instvars of the object, regardless of\any possible specialized Inspector for this type' withCRs}}.<br>
+        self typeOfSelection = #allInstVars ifTrue: [^ true].<br>
+        aMenu addTranslatedList: #(<br>
+                -<br>
+                ('objects pointing to this value'       objectReferencesToSelection)<br>
+                ('chase pointers'                                               chasePointers)<br>
+                ('explore pointers'                                     explorePointers)).<br>
+        ^ true!<br>
<br>
Item was removed:<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 added:<br>
+ ----- Method: Inspector>>browseVariableAssignments (in category 'menu commands') -----<br>
+ browseVariableAssignments<br>
+ <br>
+        self selectedInstVarName<br>
+                ifNotNil: [:instVar | self systemNavigation<br>
+                        browseAllStoresInto: instVar <br>
+                        from: self object class]<br>
+                ifNil: [self systemNavigation browseVariableAssignments: self object class]!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>browseVariableReferences (in category 'menu commands') -----<br>
+ browseVariableReferences<br>
+ <br>
+        self selectedInstVarName<br>
+                ifNotNil: [:instVar | self systemNavigation<br>
+                        browseAllAccessesTo: instVar <br>
+                        from: self object class]<br>
+                ifNil: [self systemNavigation browseVariableReferences: self object class]!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>buildValuePaneWith: (in category 'toolbuilder') -----<br>
  buildValuePaneWith: builder<br>
         | textSpec |<br>
         textSpec := builder pluggableCodePaneSpec new.<br>
+        textSpec<br>
-        textSpec <br>
                 model: self;<br>
                 name: #valuePane;<br>
+                getText: #contents;<br>
+                setText: #accept:notifying:;<br>
-                getText: #contents; <br>
-                setText: #accept:; <br>
                 editText: #typeValue:;<br>
                 help: 'Selection details.';<br>
+                selection: #contentsSelection;<br>
-                selection: #contentsSelection; <br>
                 menu: #codePaneMenu:shifted:.<br>
+        ^ textSpec!<br>
-        ^textSpec!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>buildWith: (in category 'toolbuilder') -----<br>
  buildWith: builder<br>
         "Inspector openOn: SystemOrganization"<br>
-        | windowSpec specs buttonOffset |<br>
-        buttonOffset := (Preferences standardButtonFont widthOfString: 'explore') * 3/2.<br>
         <br>
+        | windowSpec buttonOffset |<br>
+        buttonOffset := (Preferences standardButtonFont widthOfString: 'explore') * 3/2.<br>
+        windowSpec := self buildWindowWith: builder specs: {<br>
-        specs := {<br>
                 (0@0 corner: 0.3@0.71)  -> [self buildFieldListWith: builder].<br>
                 (0.3@0.0corner: 1@0.71) -> [self buildValuePaneWith: builder].<br>
                 (LayoutFrame fractions: (0@0.71 corner: 1@1) offsets: (0@0 corner: buttonOffset negated@0)) -> [self buildCodePaneWith: builder].<br>
+                (LayoutFrame fractions: (1@0.71 corner: 1@1) offsets: (buttonOffset negated@0 corner: 0 @ 0)) -> [self buildExploreButtonWith: builder].<br>
-                (LayoutFrame fractions: (1@0.71 corner: 1@1) offsets: (buttonOffset negated@0 corner: 0 @ 0)) -> [self buildExploreButtonWith: builder]<br>
         }.<br>
+        ^ builder build: windowSpec!<br>
-        <br>
-        windowSpec := self buildWindowWith: builder specs: specs. <br>
-        windowSpec extent: self initialExtent.<br>
-        ^builder build: windowSpec!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>chasePointers (in category 'menu commands') -----<br>
  chasePointers<br>
+        | selected saved |<br>
-        | selected  saved |<br>
         self selectionIndex = 0 ifTrue: [^ self changed: #flash].<br>
+        selected := self selectionOrObject.<br>
-        selected := self selection.<br>
         saved := self object.<br>
         [self object: nil.<br>
         (Smalltalk includesKey: #PointerFinder)<br>
                 ifTrue: [PointerFinder on: selected]<br>
                 ifFalse: [self inspectPointers]]<br>
+                        ensure: [self object: saved]!<br>
-                ensure: [self object: saved]!<br>
<br>
Item was changed:<br>
+ ----- Method: Inspector>>classOfSelection (in category 'accessing - selection') -----<br>
- ----- Method: Inspector>>classOfSelection (in category 'menu commands') -----<br>
  classOfSelection<br>
+        self deprecated: 'Use #selectedClass'.<br>
+        ^ self selectedClass!<br>
-        "Answer the class of the receiver's current selection"<br>
- <br>
-        self selectionUnmodifiable ifTrue: [^ object class].<br>
-        ^ self selection class!<br>
<br>
Item was changed:<br>
+ ----- Method: Inspector>>contentsIsString (in category 'accessing - selection') -----<br>
- ----- Method: Inspector>>contentsIsString (in category 'selecting') -----<br>
  contentsIsString<br>
-        "Hacked so contents empty when deselected and = long printString when item 2"<br>
  <br>
+        ^ #(allInstVars #'...') includes: (self typeOfSelection ifNil: [^ true])!<br>
-        ^ (selectionIndex = 2) | (selectionIndex = 0)!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>context: (in category 'accessing') -----<br>
  context: ctxt<br>
+        "Set the context of inspection. Currently not in use. The inst var is here because we do primitiveChangeClassTo: between subclasses (see inspect:) between different subclasses, but also context could be used as a general concept in all inspectors"<br>
-        "Set the context of inspection. Currently only used by my subclass ClosureEnvInspector. The inst var is here because we do primitiveChangeClassTo: between subclasses (see inspect:) between different subclasses, but also context could be used as a general
 concept in all inspectors"<br>
  <br>
         context := ctxt!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>copyName (in category 'menu commands') -----<br>
  copyName<br>
+        "Copy the name of the selected slot into clipboard. If the selection is a collection, refer to its first element."<br>
+ <br>
+        | name |<br>
+        name := self nameOfSelection.<br>
+        "(self selection isKindOf: Collection)<br>
+                ifTrue: [name := '({1} at: 1)' format: {name}]."<br>
+        Clipboard clipboardText: name.!<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>
-        self selectionUnmodifiable<br>
-                ifTrue: [^ self changed: #flash].<br>
-        aClass := self object class.<br>
-        variableNames := aClass allInstVarNames.<br>
-        (aClass isVariable and: [selectionIndex > (variableNames size + 2)])<br>
-                ifTrue: [sel := '(self basicAt: ' , (selectionIndex - (variableNames size + 2)) asString , ')']<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 added:<br>
+ ----- Method: Inspector>>createBaseSlotSpecs (in category 'accessing') -----<br>
+ createBaseSlotSpecs<br>
+ <br>
+        ^ OrderedDictionary newFrom: {<br>
+                (SHTextStylerST80 new styledTextFor: 'self' asText) -> #self.<br>
+                '<i>all inst vars</i>' asHtmlText -> #allInstVars }<br>
+                , (object class allInstVarNames withIndexCollect: [:name :index |<br>
+                        name -> {#instVar. index}])!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>createSlotSpecs (in category 'accessing') -----<br>
+ createSlotSpecs<br>
+ <br>
+        ^ self createBaseSlotSpecs<br>
+                , (self truncateList: ((1 to: object basicSize) collect: [:i | i asString -> {#field. i}]))!<br>
<br>
Item was changed:<br>
+ ----- Method: Inspector>>defaultIntegerBase (in category 'accessing') -----<br>
- ----- Method: Inspector>>defaultIntegerBase (in category 'selecting') -----<br>
  defaultIntegerBase<br>
         "Answer the default base in which to print integers.<br>
          Defer to the class of the instance."<br>
+        ^ (object class respondsTo: #defaultIntegerBaseInDebugger)<br>
+                ifTrue: [object class defaultIntegerBaseInDebugger]<br>
+                ifFalse: [10]!<br>
-        ^[object class defaultIntegerBaseInDebugger]<br>
-                on: MessageNotUnderstood<br>
-                do: [:ex| 10]!<br>
<br>
Item was removed:<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>
-        | 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 changed:<br>
  ----- Method: Inspector>>doItReceiver (in category 'code') -----<br>
  doItReceiver<br>
         "Answer the object that should be informed of the result of evaluating a<br>
         text selection."<br>
  <br>
+        ^ self object!<br>
-        ^object!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>dragFromFieldList: (in category 'drag-drop') -----<br>
  dragFromFieldList: index<br>
+ <br>
+        self selectionIndex: index.<br>
+        ^ self selection!<br>
-        selectionIndex = index ifFalse: [self toggleIndex: index].<br>
-        ^self selection!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>dropOnFieldList:at: (in category 'drag-drop') -----<br>
  dropOnFieldList: anObject at: index<br>
+ <br>
+        self selectionIndex: index.<br>
+        self<br>
+                replaceSelectionValue: anObject;<br>
+                update.<br>
-        selectionIndex = index ifFalse: [self toggleIndex: index].<br>
-        self replaceSelectionValue: anObject.<br>
-        self changed: #contents.<br>
         ^ true!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>explorePointers (in category 'menu commands') -----<br>
  explorePointers<br>
+ <br>
+        self typeOfSelection ifNil: [^ self changed: #flash].<br>
+        PointerExplorer openOn: self selectionOrObject.!<br>
-        self selectionIndex = 0 ifTrue: [^ self changed: #flash].<br>
-        PointerExplorer openOn: self selection.!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>exploreSelection (in category 'menu commands') -----<br>
  exploreSelection<br>
  <br>
+        ^ self selectionOrObject explore!<br>
-        self selectionIndex = 0 ifTrue: [^ self changed: #flash].<br>
-        ^ self selection explore!<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 slotSpecs keys!<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 changed:<br>
+ ----- Method: Inspector>>fieldListMenu: (in category 'menu') -----<br>
- ----- Method: Inspector>>fieldListMenu: (in category 'menu commands') -----<br>
  fieldListMenu: aMenu<br>
         "Arm the supplied menu with items for the field-list of the receiver"<br>
         ^ self menu: aMenu for: #(fieldListMenu fieldListMenuShifted:)<br>
  !<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>generateContentsString (in category 'accessing - selection') -----<br>
+ generateContentsString<br>
+ <br>
+        self typeOfSelection ifNil: [^ nil].<br>
+        ^ self contentsIsString<br>
+                ifTrue: [self selection]<br>
+                ifFalse: [self selectionPrintString]!<br>
<br>
Item was changed:<br>
+ ----- Method: Inspector>>helpText (in category 'toolbuilder') -----<br>
- ----- Method: Inspector>>helpText (in category 'accessing') -----<br>
  helpText<br>
         ^ 'evaluate expressions here'!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>i1 (in category 'accessing') -----<br>
  i1<br>
         "This is the max index shown before skipping to the <br>
         last i2 elements of very long arrays"<br>
+        self deprecated.<br>
+        ^ self maximumIndicesSize!<br>
-        ^ 100!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>i2 (in category 'accessing') -----<br>
  i2<br>
         "This is the number of elements to show at the end<br>
         of very long arrays"<br>
+        self deprecated.<br>
+        ^ self minimumLastIndicesSize!<br>
-        ^ 10!<br>
<br>
Item was changed:<br>
+ ----- Method: Inspector>>initialExtent (in category 'toolbuilder') -----<br>
- ----- Method: Inspector>>initialExtent (in category 'accessing') -----<br>
  initialExtent<br>
         "Answer the desired extent for the receiver when it is first opened on the screen.  "<br>
  <br>
         ^ 350 @ 250!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>initialize (in category 'initialize-release') -----<br>
  initialize<br>
         <br>
         selectionIndex := 0.<br>
         shouldStyleValuePane := true.<br>
+        slotSpecs := nil.<br>
         super initialize!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>inspect: (in category 'initialize-release') -----<br>
  inspect: anObject <br>
         "Initialize the receiver so that it is inspecting anObject. There is no current selection.<br>
         <br>
         Normally the receiver will be of the correct class (as defined by anObject inspectorClass),<br>
+        because it will have just been created by sending inspect to anObject.   However, the<br>
-        because it will have just been created by sedning inspect to anObject.   However, the<br>
         debugger uses two embedded inspectors, which are re-targetted on the current receiver<br>
         each time the stack frame changes.  The left-hand inspector in the debugger has its<br>
         class changed by the code here.  Care should be taken if this method is overridden to<br>
         ensure that the overriding code calls 'super inspect: anObject', or otherwise ensures that
<br>
         the class of these embedded inspectors are changed back."<br>
  <br>
+        | inspectorClass |<br>
+        inspectorClass := anObject inspectorClass.<br>
+        self class ~= inspectorClass ifTrue: [<br>
+                self class format = inspectorClass format<br>
+                        ifTrue: [self primitiveChangeClassTo: inspectorClass basicNew]<br>
+                        ifFalse: [self becomeForward: (inspectorClass basicNew copyFrom: self)]].<br>
-        | c |<br>
-        c := anObject inspectorClass.<br>
-        self class ~= c ifTrue: [<br>
-                self class format = c format<br>
-                        ifTrue: [self primitiveChangeClassTo: c basicNew]<br>
-                        ifFalse: [self becomeForward: (c basicNew copyFrom: self)]].<br>
         "Set 'object' before sending the initialize message, because some implementations<br>
         of initialize (e.g., in DictionaryInspector) require 'object' to be non-nil."<br>
         <br>
         object := anObject. <br>
         self initialize!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>inspectBasic (in category 'menu commands') -----<br>
  inspectBasic<br>
         "Bring up a non-special inspector"<br>
  <br>
+        ^ self selectionOrObject basicInspect!<br>
-        selectionIndex = 0 ifTrue: [^ object basicInspect].<br>
-        self selection basicInspect!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>inspectElement (in category 'menu commands') -----<br>
  inspectElement<br>
+        | selection size choice selectionNames choiceString |<br>
-        | sel selSize countString count nameStrs |<br>
         "Create and schedule an Inspector on an element of the receiver's model's currently selected collection."<br>
  <br>
+        selection := self selectionOrObject.<br>
+        (selection isKindOf: Inspector) ifTrue: [^ selection inspect].<br>
+        (selection isKindOf: SequenceableCollection) ifFalse:<br>
+                [^ (selection respondsTo: #inspectElement)<br>
+                        ifTrue: [selection inspectElement]<br>
+                        ifFalse: [selection inspect]].<br>
+        <br>
+        size := selection size.<br>
+        size = 1 ifTrue: [^ selection first inspect].<br>
+        <br>
+        size <= 20 ifTrue:<br>
+                [selectionNames := selection asArray withIndexCollect: [:item :index |<br>
+                        '#{1}: {2}' format: {<br>
+                                index.<br>
+                                (item printStringLimitedTo: 25) replaceAll: Character cr with: Character space }].<br>
+                choice := UIManager default chooseFrom: selectionNames title: 'Which element?'.<br>
+                choice = 0 ifTrue: [^ self].<br>
+                ^ (selection at: choice) inspect].<br>
+        <br>
+        choiceString := UIManager default request: 'Which element? (1 to ', size printString, ')' initialAnswer: '1'.<br>
+        choiceString isEmptyOrNil ifTrue: [^ self].<br>
+        selection<br>
+                at: choiceString asNumber<br>
+                ifPresent: [:item | ^ item inspect]<br>
+                ifAbsent: [Beeper beep].!<br>
-        self selectionIndex = 0 ifTrue: [^ self changed: #flash].<br>
-        ((sel := self selection) isKindOf: SequenceableCollection) ifFalse:<br>
-                [(sel respondsTo: #inspectElement) ifTrue: [^ sel inspectElement].<br>
-                ^ sel inspect].<br>
-        (selSize := sel size) = 1 ifTrue: [^ sel first inspect].<br>
-        selSize <= 20 ifTrue:<br>
-                [nameStrs := (1 to: selSize) asArray collect: [:ii | <br>
-                        ii printString, '   ', (((sel at: ii) printStringLimitedTo: 25) replaceAll: Character cr with: Character space)].<br>
-                count := UIManager default chooseFrom: (nameStrs substrings) title: 'which element?'.<br>
-                count = 0 ifTrue: [^ self].<br>
-                ^ (sel at: count) inspect].<br>
- <br>
-        countString := UIManager default request: 'Which element? (1 to ', selSize printString, ')' initialAnswer: '1'.<br>
-        countString isEmptyOrNil ifTrue: [^ self].<br>
-        count := Integer readFrom: (ReadStream on: countString).<br>
-        (count > 0 and: [count <= selSize])<br>
-                ifTrue: [(sel at: count) inspect]<br>
-                ifFalse: [Beeper beep]!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>inspectSelection (in category 'menu commands') -----<br>
  inspectSelection<br>
         "Create and schedule an Inspector on the receiver's model's currently selected object."<br>
  <br>
+        self typeOfSelection ifNil: [^ self changed: #flash].<br>
+        ^ self selectionOrObject inspect!<br>
-        self selectionIndex = 0 ifTrue: [^ self changed: #flash].<br>
-        self selection inspect.<br>
-        ^ self selection!<br>
<br>
Item was changed:<br>
+ ----- Method: Inspector>>inspectorKey:from: (in category 'menu') -----<br>
- ----- Method: Inspector>>inspectorKey:from: (in category 'menu commands') -----<br>
  inspectorKey: aChar from: view<br>
         "Respond to a Command key issued while the cursor is over my field list"<br>
  <br>
+        ^ aChar<br>
+                caseOf: {<br>
+                        [$i]    ->      [self inspectSelection].<br>
+                        [$I]    ->      [self exploreSelection].<br>
+                        [$b]    ->      [self browseClass].<br>
+                        [$h]    ->      [self classHierarchy].<br>
+                        [$p]    ->      [self browseFullProtocol].<br>
+                        [$r]    ->      [self browseVariableReferences].<br>
+                        [$a]    ->      [self browseVariableAssignments].<br>
+                        [$N]    ->      [self browseClassRefs].<br>
+                        [$c]    ->      [self copyName].<br>
+                        [$t]    ->      [self tearOffTile].<br>
+                        [$v]    ->      [self viewerForValue] }<br>
+                otherwise:      [self arrowKey: aChar from: view]!<br>
-        aChar == $i ifTrue: [^ self selection inspect].<br>
-        aChar == $I ifTrue: [^ self selection explore].<br>
-        aChar == $b ifTrue:     [^ self browseClass].<br>
-        aChar == $h ifTrue:     [^ self classHierarchy].<br>
-        aChar == $c ifTrue: [^ self copyName].<br>
-        aChar == $p ifTrue: [^ self browseFullProtocol].<br>
-        aChar == $N ifTrue: [^ self browseClassRefs].<br>
-        aChar == $t ifTrue: [^ self tearOffTile].<br>
-        aChar == $v ifTrue: [^ self viewerForValue].<br>
- <br>
-        ^ self arrowKey: aChar from: view!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>inspectorOverflowText (in category 'toolbuilder') -----<br>
+ inspectorOverflowText<br>
+ <br>
+        ^ ('<Elements {1} to {2} not shown!! To inspect a certain element, {3}>' asText<br>
+                addAttribute: TextEmphasis italic;<br>
+                format: {<br>
+                        self maximumIndicesSize - self minimumLastIndicesSize.<br>
+                        (self slotSpecs atIndex: self selectionIndex + 1) value second - 1.<br>
+                        Smalltalk isMorphic<br>
+                                ifTrue: ['click here' asText<br>
+                                        addAttribute: (PluggableTextAttribute evalBlock: [self inspectElement]);<br>
+                                        yourself]<br>
+                                ifFalse: ['open the field list menu and choose "inspect element"'] })!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>instVarsPrintString (in category 'accessing') -----<br>
+ instVarsPrintString<br>
+ <br>
+        ^ [object longPrintStringLimitedTo: 20000]<br>
+                on: Error<br>
+                do: [self printStringErrorText]!<br>
<br>
Item was changed:<br>
+ ----- Method: Inspector>>mainFieldListMenu: (in category 'menu') -----<br>
- ----- Method: Inspector>>mainFieldListMenu: (in category 'menu commands') -----<br>
  mainFieldListMenu: aMenu<br>
         "Arm the supplied menu with items for the field-list of the receiver"<br>
         <fieldListMenu><br>
+        "gets overriden by subclasses, _without_ the <fieldListMenu>"<br>
-        "gets overriden by subclasses, _whithout_ the <fieldListMenu>"<br>
         aMenu addStayUpItemSpecial.<br>
+        <br>
+        self addObjectItemsTo: aMenu.<br>
- <br>
-        aMenu addList: #(<br>
-                ('inspect (i)'                                          inspectSelection)<br>
-                ('explore (I)'                                          exploreSelection)).<br>
- <br>
         self addCollectionItemsTo: aMenu.<br>
+        aMenu addLine.<br>
+        self typeOfSelection = #instVar<br>
+                ifTrue: [<br>
+                        self addInstVarItemsTo: aMenu].<br>
+        self addFieldItemsTo: aMenu.<br>
+        aMenu addLine.<br>
+        self addClassItemsTo: aMenu.<br>
+        <br>
+        (Smalltalk isMorphic and: [self selectionIsSpecial not])<br>
+                ifTrue: [<br>
+                        aMenu addLine.<br>
+                        self addMorphicItemsTo: aMenu].<br>
  <br>
+        ^ aMenu!<br>
-        aMenu addList: #(<br>
-                -<br>
-                ('method refs to this inst var'         referencesToSelection)<br>
-                ('methods storing into this inst var'   defsOfSelection)<br>
-                ('objects pointing to this value'               objectReferencesToSelection)<br>
-                ('chase pointers'                                       chasePointers)<br>
-                ('explore pointers'                             explorePointers)<br>
-                -<br>
-                ('browse full (b)'                                      browseClass)<br>
-                ('browse hierarchy (h)'                         classHierarchy)<br>
-                ('browse protocol (p)'                          browseFullProtocol)<br>
-                -<br>
-                ('references... (r)'                                    browseVariableReferences)<br>
-                ('assignments... (a)'                           browseVariableAssignments)<br>
-                ('class refs (N)'                                               browseClassRefs)<br>
-                -<br>
-                ('copy name (c)'                                        copyName)              
<br>
-                ('basic inspect'                                                inspectBasic)).<br>
- <br>
-        Smalltalk isMorphic ifTrue:<br>
-                [aMenu addList: #(<br>
-                        -<br>
-                        ('tile for this value   (t)'                    tearOffTile)<br>
-                        ('viewer for this value (v)'            viewerForValue))].<br>
- <br>
-        ^ aMenu<br>
- <br>
- <br>
- "                     -<br>
-                        ('alias for this value'                 aliasForValue)<br>
-                        ('watcher for this slot'                        watcherForSlot)"<br>
- <br>
- !<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>maximumIndicesSize (in category 'accessing') -----<br>
+ maximumIndicesSize<br>
+        "The maximum number of field slots that can be displayed. If there are more, they will be abbreviated."<br>
+ <br>
+        ^ 100!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>minimumLastIndicesSize (in category 'accessing') -----<br>
+ minimumLastIndicesSize<br>
+        "The minimum number of last slots to display if the list is abbreviated due to exceed of #maximumIndicesSize"<br>
+ <br>
+        ^ 10!<br>
<br>
Item was changed:<br>
+ ----- Method: Inspector>>modelWakeUpIn: (in category 'stepping') -----<br>
- ----- Method: Inspector>>modelWakeUpIn: (in category 'accessing') -----<br>
  modelWakeUpIn: aWindow<br>
+ <br>
+        self<br>
+                updateListsAndCodeIn: aWindow;<br>
+                refreshContentsIfChanged.!<br>
-        | newText |<br>
-        self updateListsAndCodeIn: aWindow.<br>
-        newText := self contentsIsString<br>
-                ifTrue: [newText := self selection]<br>
-                ifFalse: ["keep it short to reduce time to compute it"<br>
-                        self selectionPrintString ].<br>
-        newText = contents ifFalse:<br>
-                [contents := newText.<br>
-                self changed: #contents]!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>nameOfSelection (in category 'accessing - selection') -----<br>
+ nameOfSelection<br>
+ <br>
+        ^ self typeOfSelection caseOf: {<br>
+                [#self] -> ['self'].<br>
+                [#allInstVars] -> ['self longPrintString'].<br>
+                [#instVar] -> [self selectedInstVarName].<br>
+                [#field] -> ['(self basicAt: {1})' format: {self selectedObjectIndex}]<br>
+        }!<br>
<br>
Item was changed:<br>
+ ----- Method: Inspector>>noteSelectionIndex:for: (in category 'selecting') -----<br>
- ----- Method: Inspector>>noteSelectionIndex:for: (in category 'accessing') -----<br>
  noteSelectionIndex: anInteger for: aSymbol<br>
         aSymbol == #fieldList<br>
                 ifTrue:<br>
                         [selectionIndex := anInteger]!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>object: (in category 'accessing') -----<br>
  object: anObject <br>
         "Set anObject to be the object being inspected by the receiver."<br>
  <br>
+        | oldSlot |<br>
-        | oldSelection oldFields newFields commonFieldRange |<br>
         anObject == object<br>
+                ifTrue: [^ self update].<br>
+        oldSlot := self selectedSlotName.<br>
+        self inspect: anObject.<br>
+        self changed: #inspectObject.<br>
+        self selectSlotNamed: oldSlot.<br>
+        self<br>
+                changed: #fieldList;<br>
+                changed: #contents;<br>
+                changed: #helpText.!<br>
-                ifTrue: [self update]<br>
-                ifFalse:<br>
-                        [oldSelection := selectionIndex.<br>
-                        oldFields := self fieldList.<br>
-                        self inspect: anObject.<br>
-                        newFields := self fieldList.<br>
-                        commonFieldRange := ((1 to: (oldFields size min: newFields size))<br>
-                                select: [:i | (oldFields at: i) = (newFields at: i)])<br>
-                                        ifNotEmpty: #last<br>
-                                        ifEmpty: [0].<br>
-                        self changed: #inspectObject.<br>
-                        self toggleIndex: (oldSelection <= commonFieldRange<br>
-                                ifTrue: [oldSelection]<br>
-                                ifFalse: [0]).<br>
-                        self changed: #fieldList.<br>
-                        self changed: #contents.<br>
-                        self changed: #helpText]!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>objectReferencesToSelection (in category 'menu commands') -----<br>
  objectReferencesToSelection<br>
         "Open a list inspector on all the objects that point to the value of the selected instance variable, if any.  "<br>
  <br>
+        self typeOfSelection ifNil: [^ self changed: #flash].<br>
-        self selectionIndex = 0 ifTrue: [^ self changed: #flash].<br>
         self systemNavigation<br>
+                browseAllObjectReferencesTo: self selectionOrObject<br>
-                browseAllObjectReferencesTo: self selection<br>
                 except: (Array with: self object)<br>
                 ifNone: [:obj | self changed: #flash].<br>
  !<br>
<br>
Item was changed:<br>
+ ----- Method: Inspector>>printStringErrorText (in category 'toolbuilder') -----<br>
- ----- Method: Inspector>>printStringErrorText (in category 'private') -----<br>
  printStringErrorText<br>
+ <br>
+        | command |<br>
+        command := self typeOfSelection = #allInstVars<br>
+                ifTrue: ['self longPrintString']<br>
+                ifFalse: ['{1} printString' format: {self nameOfSelection}].<br>
+        ^ '<{1} evaluate "{2}" to debug>' asText<br>
+                addAttribute: TextColor red;<br>
+                format: {<br>
+                        '<b>error in #printString:</b>' asHtmlText.<br>
+                        Smalltalk isMorphic<br>
+                                ifTrue: [command asText<br>
+                                        addAttribute: (PluggableTextAttribute evalBlock: [Compiler evaluate: command for: self object]);<br>
+                                        yourself]<br>
+                                ifFalse: [command] }!<br>
-        | nm |<br>
-        nm := self selectionIndex < 3<br>
-                ifTrue: ['self']<br>
-                ifFalse: [self selectedSlotName].<br>
-        ^ (nm<br>
-                ifNil: ['no selection']<br>
-                ifNotNil:<br>
-                        [nm first isDigit<br>
-                                ifTrue: ['<error in printString: evaluate "(self at: ' , nm , ') printString" to debug>']<br>
-                                ifFalse: ['<error in printString: evaluate "' , nm , ' printString" to debug>'] ]) asText!<br>
<br>
Item was removed:<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.  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 added:<br>
+ ----- Method: Inspector>>refreshContentsIfChanged (in category 'updating') -----<br>
+ refreshContentsIfChanged<br>
+        <br>
+        | newText |<br>
+        newText := self generateContentsString.<br>
+        newText = contents ifTrue: [^ self].<br>
+        <br>
+        contents := newText.<br>
+        shouldStyleValuePane := false.<br>
+        self changed: #contents.!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>refreshSlots (in category 'accessing') -----<br>
+ refreshSlots<br>
+ <br>
+        slotSpecs := nil.<br>
+        self changed: #fieldList.<br>
+        self update.!<br>
<br>
Item was changed:<br>
+ ----- Method: Inspector>>replaceSelectionValue: (in category 'code') -----<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>
+        | instVarIndex |<br>
+        self selectionUnmodifiable ifTrue: [<br>
+                ^ self object].<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>
+        object class isVariable ifFalse: [<br>
+                self error: 'Cannot replace selection'].<br>
+        object at: self selectedObjectIndex put: anObject!<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>>representsSameBrowseeAs: (in category 'morphic ui') -----<br>
  representsSameBrowseeAs: anotherInspector<br>
+ <br>
         ^ self object == anotherInspector object!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>selectSlotNamed: (in category 'selecting') -----<br>
+ selectSlotNamed: aSlotName<br>
+        "Select the slot that is labeled aSlotName, or nothing, is there is no match."<br>
+ <br>
+        self selectionIndex: (self fieldList indexOf: aSlotName ifAbsent: [0])<br>
+        !<br>
<br>
Item was changed:<br>
+ ----- Method: Inspector>>selectedClass (in category 'accessing - selection') -----<br>
- ----- Method: Inspector>>selectedClass (in category 'accessing') -----<br>
  selectedClass<br>
         "Answer the class of the receiver's current selection"<br>
  <br>
+        ^ self selectionOrObject class!<br>
-        self selectionUnmodifiable ifTrue: [^ object class].<br>
-        ^ self selection class!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>selectedIndexOf: (in category 'accessing - selection') -----<br>
+ selectedIndexOf: aSymbol<br>
+ <br>
+        ^ (self slotSpecs atIndex: self selectionIndex) value second!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>selectedInstVarName (in category 'accessing - selection') -----<br>
+ selectedInstVarName<br>
+ <br>
+        self typeOfSelection = #instVar ifFalse: [^ nil].<br>
+        ^ self object class allInstVarNames<br>
+                at: (self selectedIndexOf: #instVar)!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>selectedObjectIndex (in category 'accessing - selection') -----<br>
+ selectedObjectIndex<br>
+        "Answer the index of the inspectee's collection that the current selection refers to."<br>
+ <br>
+        ^ self selectedIndexOf: #field!<br>
<br>
Item was changed:<br>
+ ----- Method: Inspector>>selection (in category 'accessing - selection') -----<br>
- ----- Method: Inspector>>selection (in category 'selecting') -----<br>
  selection<br>
+        "Answer the value of the selected variable slot."<br>
+        <br>
+        ^ self typeOfSelection caseOf: {<br>
+                [nil] -> [nil].<br>
+                [#self] -> [object].<br>
+                [#allInstVars] -> [self instVarsPrintString].<br>
+                [#'...'] -> [self inspectorOverflowText].<br>
+                [#instVar] -> [object instVarAt: (self selectedIndexOf: #instVar)].<br>
+                [#field] -> [object basicAt: (self selectedIndexOf: #field)].<br>
+        }!<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<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>>selectionIndex (in category 'selecting') -----<br>
  selectionIndex<br>
-        "The receiver has a list of variables of its inspected object. One of these
<br>
-        is selected. Answer the index into the list of the selected variable."<br>
  <br>
+        ^ selectionIndex!<br>
-        ^selectionIndex!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>selectionIndex: (in category 'selecting') -----<br>
+ selectionIndex: anIndex<br>
+ <br>
+        self selectionIndex = anIndex<br>
+                ifFalse: [self toggleIndex: anIndex]!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>selectionIsSpecial (in category 'accessing - selection') -----<br>
+ selectionIsSpecial<br>
+        "Returns whether the selected slot does not represent a real object"<br>
+ <br>
+        ^ #(allInstVars #'...') includes: self typeOfSelection!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>selectionOrObject (in category 'accessing - selection') -----<br>
+ selectionOrObject<br>
+        "My selection. If nothing useful is selected, return my inspectee instead."<br>
+ <br>
+        ^ ({ nil. #'...' } includes: self typeOfSelection)<br>
+                ifFalse: [self selection]<br>
+                ifTrue: [self object]!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>selectionPrintString (in category 'selecting') -----<br>
  selectionPrintString<br>
         | text |<br>
+        selectionUpdateTime := [<br>
+                text := [<br>
+                        | selection |<br>
+                        selection := self selection.<br>
+                        selection isInteger<br>
+                                ifTrue: [selection storeStringBase: self defaultIntegerBase]<br>
+                                ifFalse: [selection printStringLimitedTo: 5000]]<br>
+                                                on: Error do: [self printStringErrorText]]<br>
+                                                                timeToRun.<br>
-        selectionUpdateTime := [text := [self selection isInteger<br>
-                                                                                ifTrue: [self selection storeStringBase: self defaultIntegerBase]<br>
-                                                                                ifFalse: [self selection printStringLimitedTo: 5000]]<br>
-                                                on: Error<br>
-                                                do: [text := self printStringErrorText.<br>
-                                                        text<br>
-                                                                addAttribute: TextColor red<br>
-                                                                from: 1<br>
-                                                                to: text size.<br>
-                                                        text]] timeToRun.<br>
         ^ text!<br>
<br>
Item was changed:<br>
+ ----- Method: Inspector>>selectionUnmodifiable (in category 'accessing - selection') -----<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 example, a selection of 'self' or 'all inst vars' is unmodifiable."<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>
+        ^ { nil. #self. #allInstVars. #'...' } includes: self typeOfSelection!<br>
-        ^ selectionIndex <= 2!<br>
<br>
Item was changed:<br>
+ ----- Method: Inspector>>setExpression: (in category 'accessing') -----<br>
- ----- Method: Inspector>>setExpression: (in category 'code') -----<br>
  setExpression: aString<br>
  <br>
         self expression: aString.<br>
         self changed: #expression.!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>slotSpecs (in category 'accessing') -----<br>
+ slotSpecs<br>
+ <br>
+        ^ slotSpecs ifNil: [slotSpecs := self createSlotSpecs]!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>stepAt:in: (in category 'stepping') -----<br>
  stepAt: millisecondClockValue in: aWindow<br>
-        | newText |<br>
  <br>
         (Preferences smartUpdating and: [(millisecondClockValue - self timeOfLastListUpdate) > 8000]) "Not more often than once every 8 seconds"<br>
                 ifTrue:<br>
                         [self updateListsAndCodeIn: aWindow.<br>
                         timeOfLastListUpdate := millisecondClockValue].<br>
  <br>
+        self refreshContentsIfChanged.!<br>
-        newText := self contentsIsString<br>
-                ifTrue: [self selection]<br>
-                ifFalse: ["keep it short to reduce time to compute it"<br>
-                        self selectionPrintString ].<br>
-        newText = contents ifFalse:<br>
-                [contents := newText.<br>
-                self changed: #contents]!<br>
<br>
Item was changed:<br>
+ ----- Method: Inspector>>stepTimeIn: (in category 'stepping') -----<br>
- ----- Method: Inspector>>stepTimeIn: (in category 'accessing') -----<br>
  stepTimeIn: aSystemWindow<br>
         ^ (selectionUpdateTime ifNil: [0]) * 10 max: 1000!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>toggleIndex: (in category 'selecting') -----<br>
  toggleIndex: anInteger<br>
         "The receiver has a list of variables of its inspected object. One of these
<br>
         is selected. If anInteger is the index of this variable, then deselect it.
<br>
         Otherwise, make the variable whose index is anInteger be the selected <br>
         item."<br>
  <br>
         selectionUpdateTime := 0.<br>
         selectionIndex = anInteger<br>
                 ifTrue: <br>
                         ["same index, turn off selection"<br>
                         selectionIndex := 0.<br>
                         contents := '']<br>
                 ifFalse:<br>
                         ["different index, new selection"<br>
                         shouldStyleValuePane := false.<br>
                         selectionIndex := anInteger.<br>
+                        contents := self generateContentsString].<br>
+        self<br>
+                changed: #selection;<br>
+                changed: #contents;<br>
+                changed: #selectionIndex.!<br>
-                        self contentsIsString<br>
-                                ifTrue: [contents := self selection]<br>
-                                ifFalse: [contents := self selectionPrintString]].<br>
-        self changed: #selection.<br>
-        self changed: #contents.<br>
-        self changed: #selectionIndex.!<br>
<br>
Item was removed:<br>
- ----- Method: Inspector>>trash (in category 'accessing') -----<br>
- trash<br>
-        "What goes in the bottom pane"<br>
-        ^ ''!<br>
<br>
Item was removed:<br>
- ----- Method: Inspector>>trash: (in category 'accessing') -----<br>
- trash: newText<br>
-        "Don't save it"<br>
-        ^ true!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>truncateList: (in category 'private') -----<br>
+ truncateList: aList<br>
+ <br>
+        ^ aList size <= self maximumIndicesSize<br>
+                ifTrue: [aList]<br>
+                ifFalse: [(aList first: self maximumIndicesSize - self minimumLastIndicesSize - 1)<br>
+                        , {'...' -> #'...'}<br>
+                        , (aList last: self minimumLastIndicesSize)]!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>typeOfSelection (in category 'accessing - selection') -----<br>
+ typeOfSelection<br>
+ <br>
+        ^ self slotSpecs values<br>
+                at: self selectionIndex<br>
+                ifPresent: [:entry | entry isSymbol ifTrue: [entry] ifFalse: [entry first]]<br>
+                ifAbsent: [nil]!<br>
<br>
Item was changed:<br>
+ ----- Method: Inspector>>typeValue: (in category 'styling') -----<br>
- ----- Method: Inspector>>typeValue: (in category 'selecting') -----<br>
  typeValue: aTextOrString<br>
  <br>
         shouldStyleValuePane := true.<br>
         self changed: #style!<br>
<br>
Item was changed:<br>
+ ----- Method: Inspector>>update (in category 'updating') -----<br>
- ----- Method: Inspector>>update (in category 'accessing') -----<br>
  update<br>
         "Reshow contents, assuming selected value may have changed."<br>
  <br>
+        selectionIndex = 0 ifTrue: [^ self].<br>
+        contents := self generateContentsString.<br>
+        shouldStyleValuePane := false.<br>
+        self<br>
+                changed: #contents;<br>
+                changed: #selection; flag: #ct; "Is there any update method that cares for #selection? Found none."<br>
+                changed: #selectionIndex.!<br>
-        selectionIndex = 0<br>
-                ifFalse:<br>
-                        [self contentsIsString<br>
-                                ifTrue: [contents := self selection]<br>
-                                ifFalse: [contents := self selectionPrintString].<br>
-                        self changed: #contents.<br>
-                        self changed: #selection.<br>
-                        self changed: #selectionIndex]!<br>
<br>
Item was added:<br>
+ ----- Method: Inspector>>updateEntries (in category 'accessing') -----<br>
+ updateEntries<br>
+ <br>
+        slotSpecs := nil.<br>
+        self changed: #fieldList.<br>
+        self update.!<br>
<br>
Item was changed:<br>
  ----- Method: Inspector>>viewerForValue (in category 'menu commands') -----<br>
  viewerForValue<br>
         "Open up a viewer on the value of the receiver's current selection"<br>
  <br>
+        self selectionOrObject beViewed!<br>
-        | objectToRepresent |<br>
-        objectToRepresent := self selectionIndex = 0 ifTrue: [object] ifFalse: [self selection].<br>
-        objectToRepresent beViewed<br>
-        !<br>
<br>
Item was changed:<br>
+ ----- Method: Inspector>>wantsSteps (in category 'stepping') -----<br>
- ----- Method: Inspector>>wantsSteps (in category 'accessing') -----<br>
  wantsSteps<br>
         ^ true!<br>
<br>
Item was added:<br>
+ ----- Method: OrderedCollectionInspector>>createSlotSpecs (in category 'accessing') -----<br>
+ createSlotSpecs<br>
+ <br>
+        object ifNil: [ ^ OrderedDictionary new].<br>
+        ^ (self createBaseSlotSpecs first: 2) , (self truncateList:<br>
+                ((1 to: self objectSize) collect: [:i | i printString -> {#field. i}]))!<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 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>
+        self typeOfSelection = #field<br>
+                ifFalse: [^ super replaceSelectionValue: anObject].<br>
+        ^ object at: self selectedObjectIndex put: anObject!<br>
-        (selectionIndex - 2) <= object class instSize<br>
-                ifTrue: [^ super replaceSelectionValue: anObject].<br>
-        object at: self selectedObjectIndex put: anObject!<br>
<br>
Item was removed:<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 - 2 - object class instSize.<br>
-        ^ (object size <= (self i1 + self i2)  or: [basicIndex <= self i1])<br>
-                ifTrue: [basicIndex]<br>
-                ifFalse: [object size - (self i1 + self i2) + basicIndex]!<br>
<br>
Item was changed:<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>
+        self typeOfSelection = #field<br>
+                ifFalse: [^ super selection].<br>
-        (selectionIndex - 2) <= object class instSize<br>
-                ifTrue: [^ super selection].<br>
         ^ object at: self selectedObjectIndex!<br>
<br>
Item was added:<br>
+ ----- Method: SetInspector>>addCollectionItemsTo: (in category 'menu') -----<br>
+ addCollectionItemsTo: aMenu<br>
+ <br>
+        super addCollectionItemsTo: aMenu.<br>
+        aMenu addTranslatedList: #(<br>
+                ('refresh view'                 update)).!<br>
<br>
Item was added:<br>
+ ----- Method: SetInspector>>addFieldItemsTo: (in category 'menu') -----<br>
+ addFieldItemsTo: aMenu<br>
+ <br>
+        (super addFieldItemsTo: aMenu)<br>
+                ifFalse: [^ false].<br>
+        self typeOfSelection = #field<br>
+                ifFalse: [^ false].<br>
+        aMenu addTranslatedList: #(<br>
+                ('remove'       removeSelection)).<br>
+        ^ true!<br>
<br>
Item was removed:<br>
- ----- Method: SetInspector>>arrayIndexForSelection (in category 'selecting') -----<br>
- arrayIndexForSelection<br>
-        ^ (self fieldList at: selectionIndex) asInteger!<br>
<br>
Item was removed:<br>
- ----- Method: SetInspector>>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 |<br>
-        self selectionIndex <= (2 + object class instSize)<br>
-                ifTrue: [super copyName]<br>
-                ifFalse: [sel := '(self array at: '<br>
-                                                , (String streamContents: <br>
-                                                        [:strm | self arrayIndexForSelection storeOn: strm]) , ')'.<br>
-                        Clipboard clipboardText: sel asText]!<br>
<br>
Item was added:<br>
+ ----- Method: SetInspector>>createSlotSpecs (in category 'accessing') -----<br>
+ createSlotSpecs<br>
+ <br>
+        object ifNil: [^ OrderedDictionary new].<br>
+        ^ (self createBaseSlotSpecs first: 2) , self itemSpecs<br>
+ !<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 added:<br>
+ ----- Method: SetInspector>>inspectorOverflowText (in category 'toolbuilder') -----<br>
+ inspectorOverflowText<br>
+ <br>
+        ^ ('<{1} more elements not shown!!>' format: {self object size - self maximumIndicesSize})<br>
+                asText<br>
+                        addAttribute: TextEmphasis italic;<br>
+                        yourself!<br>
<br>
Item was added:<br>
+ ----- Method: SetInspector>>itemSpecs (in category 'accessing') -----<br>
+ itemSpecs<br>
+ <br>
+        | items |<br>
+        items := (object asArray<br>
+                withIndexCollect: [:each :i | each ifNotNil: [i]])<br>
+                select: #notNil.<br>
+        ^ self truncateList: (items collect: [:each |<br>
+                each asString -> {#field. each}])!<br>
<br>
Item was removed:<br>
- ----- Method: SetInspector>>mainFieldListMenu: (in category 'menu') -----<br>
- mainFieldListMenu: aMenu<br>
- <br>
-        ^ aMenu addTranslatedList: #(<br>
-                        ('inspect'                                                      inspectSelection)<br>
-                        ('copy name'                                            copyName)<br>
-                        ('objects pointing to this value'               objectReferencesToSelection)<br>
-                        ('refresh view'                                         update)<br>
-                        ('remove'                                                       removeSelection)<br>
-                        -<br>
-                        ('basic inspect'                                                inspectBasic));<br>
-                yourself<br>
- !<br>
<br>
Item was added:<br>
+ ----- Method: SetInspector>>nameOfSelection (in category 'accessing - selection') -----<br>
+ nameOfSelection<br>
+ <br>
+        self typeOfSelection = #field ifFalse: [<br>
+                ^ super nameOfSelection].<br>
+        ^ '(self array at: {1})' format: {self selectedIndexOf: #field}!<br>
<br>
Item was changed:<br>
+ ----- Method: SetInspector>>removeSelection (in category 'menu commands') -----<br>
- ----- Method: SetInspector>>removeSelection (in category 'menu') -----<br>
  removeSelection<br>
+        <br>
+        self typeOfSelection = #field ifFalse: [^ self changed: #flash].<br>
-        (selectionIndex <= object class instSize) ifTrue: [^ self changed: #flash].<br>
         object remove: self selection.<br>
         selectionIndex := 0.<br>
+        self updateEntries.!<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: SetInspector>>replaceSelectionValue: (in category 'accessing - selection') -----<br>
- ----- Method: SetInspector>>replaceSelectionValue: (in category 'selecting') -----<br>
  replaceSelectionValue: anObject<br>
+ <br>
+        self typeOfSelection = #field<br>
+                ifFalse: [^ super replaceSelectionValue: anObject].<br>
+        ^ object array at: (self selectedIndexOf: #field) put: anObject!<br>
-        ^ object array at: self arrayIndexForSelection put: anObject!<br>
<br>
Item was changed:<br>
+ ----- Method: SetInspector>>selection (in category 'accessing - selection') -----<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>
+        self typeOfSelection = #field<br>
+                ifFalse: [^ super selection].<br>
+        ^ object array at: (self selectedIndexOf: #field)!<br>
-        ^ object array at: self arrayIndexForSelection ifAbsent: [ String empty ]!<br>
<br>
Item was changed:<br>
  ----- Method: StandardToolSet class>>inspect:label: (in category 'inspecting') -----<br>
  inspect: anObject label: aString<br>
         "Open an inspector on the given object. The tool set must know which inspector type to use for which object - the object cannot possibly know what kind of inspectors the toolset provides."<br>
+        ^ anObject inspectorClass openOn: anObject withLabel: aString!<br>
-        ^ anObject inspectorClass openOn: anObject withEvalPane: true withLabel: aString!<br>
<br>
Item was changed:<br>
  SetInspector subclass: #WeakSetInspector<br>
         instanceVariableNames: 'flagObject'<br>
         classVariableNames: ''<br>
         poolDictionaries: ''<br>
         category: 'Tools-Inspector'!<br>
  <br>
+ !WeakSetInspector commentStamp: 'ct 9/27/2019 19:18' prior: 0!<br>
+ A version of the SetInspector specialized for inspecting WeakSets.  It knows about the flag object used to indicate empty locations in the hash table.!<br>
- !WeakSetInspector commentStamp: '<historical>' prior: 0!<br>
- A verison of the SetInspector specialized for inspecting WeakSets.  It knows about the flag object used to indicate empty locations in the hash table.!<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>>itemSpecs (in category 'accessing') -----<br>
+ itemSpecs<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 -> {#field. i}]].<br>
+        <br>
+        ^ slotIndices contents!<br>
<br>
<br>
</div>
</span></font>
</body>
</html>