added:
authorClaus Gittinger <cg@exept.de>
Sat, 06 Feb 2010 18:57:29 +0100
changeset 9367 0f2dbaf97046
parent 9366 58c82c246a2f
child 9368 fda7e1ae93f6
added: #indexOfFirstNamedInstvarInList #namedFieldAt: #namedFieldAt:put: variable renamed in:21 methods changed:14 methods
InspectorView.st
--- a/InspectorView.st	Thu Feb 04 23:20:17 2010 +0100
+++ b/InspectorView.st	Sat Feb 06 18:57:29 2010 +0100
@@ -291,7 +291,7 @@
 
     |aList sameObject|
 
-    sameObject := anObject == inspectedObject and:[inspectedObject notNil].
+    sameObject := anObject == object and:[object notNil].
     inspectedObject := object := anObject.
 
     sameObject ifTrue:[
@@ -405,16 +405,16 @@
 
     |oldSelection|
 
-    changedObject == inspectedObject ifTrue:[
+    changedObject == object ifTrue:[
         oldSelection := listView selection.
-        self inspect:inspectedObject.
+        self inspect:object.
         oldSelection notNil ifTrue:[
             self showSelection:oldSelection
         ]
     ].
 
-    changedObject == inspectedObjectHolder ifTrue:[
-        self inspect:(inspectedObjectHolder value)
+    changedObject == object ifTrue:[
+        self inspect:(object value)
     ].
 
     super update:something with:aParameter from:changedObject
@@ -571,12 +571,12 @@
 
     super realize.
     "/ cg: I dont remember what this was needed for (is it still?)
-    false "inspectedObject notNil" ifTrue:[
+    false "object notNil" ifTrue:[
         "
          kludge to trick inspect:, which ignores setting the
          same object again ...
         "
-        o := inspectedObject.
+        o := object.
         inspectedObject := object := nil.
         self inspect:o
     ]
@@ -693,7 +693,7 @@
     ].
 
     protocols := Dictionary new.
-    inspectedObject class withAllSuperclassesDo:[:eachClass |
+    object class withAllSuperclassesDo:[:eachClass |
         eachClass methodDictionary keysAndValuesDo:[:sel :m |
             sel numArgs == 0 ifTrue:[
                 (protocols at:m category ifAbsentPut:[Set new]) add:sel.
@@ -776,7 +776,7 @@
     |sel|
 
     sel := self selection.
-    (inspectedObject isFilename or:[sel isFilename]) ifTrue:[
+    (object isFilename or:[sel isFilename]) ifTrue:[
         ^ #(
                ('Open FileBrowser'             #openFileBrowser)
           ).
@@ -797,7 +797,7 @@
                        ('Browse Blocks Home'           #browseHome)
               ).
     ].
-    (inspectedObject isMethod or:[sel isMethod]) ifTrue:[
+    (object isMethod or:[sel isMethod]) ifTrue:[
         items := items , #(
                        ('Browse Methods Class'         #browseMethodsClass)
                  ).
@@ -965,7 +965,7 @@
         inspectHistory isNil ifTrue:[
             inspectHistory := OrderedCollection new
         ].
-        inspectHistory addLast:inspectedObject.
+        inspectHistory addLast:object.
         self inspect:objectToInspect.
     ]
 
@@ -1016,7 +1016,7 @@
 doTraceAll
     "place a trace on all messages sent to the inspected object"
 
-    self topView withWaitCursorDo:[MessageTracer traceAll:inspectedObject on:Transcript]
+    self topView withWaitCursorDo:[MessageTracer traceAll:object on:Transcript]
 !
 
 doTrap
@@ -1032,27 +1032,25 @@
         selector isNil ifTrue:[
             self warn:'no such selector'
         ] ifFalse:[
-            self topView withWaitCursorDo:[MessageTracer trap:inspectedObject 
+            self topView withWaitCursorDo:[MessageTracer trap:object 
                                                          selector:selector]
         ]
     ]
 
     "Modified: 12.4.1996 / 14:07:01 / cg"
-
-
 !
 
 doTrapAll
     "place a trap on all messages sent to the inspected object"
 
-    self topView withWaitCursorDo:[MessageTracer trapAll:inspectedObject]
+    self topView withWaitCursorDo:[MessageTracer trapAll:object]
 !
 
 doTrapAnyInstVarChange
     "place a trap which is triggered if any instVar of the inspected object is changed"
 
     self topView withWaitCursorDo:[
-        MessageTracer trapModificationsIn:inspectedObject
+        MessageTracer trapModificationsIn:object
     ]
 !
 
@@ -1069,15 +1067,15 @@
             ^ self.
         ].
         MessageTracer 
-                trapModificationsOf:(inspectedObject class allInstVarNames at:idx)
-                in:inspectedObject
+                trapModificationsOf:(object class allInstVarNames at:idx)
+                in:object
     ]
 !
 
 doUntrace
     "remove traps/traces"
 
-    MessageTracer untrace:inspectedObject
+    MessageTracer untrace:object
 !
 
 inspectOwners
@@ -1087,7 +1085,7 @@
     self withCursor:(Cursor questionMark) do:[
         |owners dict|
 
-        owners := (ObjectMemory whoReferences:inspectedObject) asOrderedCollection.
+        owners := (ObjectMemory whoReferences:object) asOrderedCollection.
         owners size > 500 ifTrue:[
             (self confirm:'there are ' , owners size printString , ' owners.\\Do you really want to see them all ?' withCRs)
             ifFalse:[^ self]
@@ -1101,14 +1099,14 @@
                 names := owner class allInstVarNames.
                 oClass := owner class.
                 1 to:oClass instSize do:[:i |
-                    (owner instVarAt:i) == inspectedObject ifTrue:[
+                    (owner instVarAt:i) == object ifTrue:[
                         set add:(names at:i).
                     ].
                 ].
                 oClass isVariable ifTrue:[
                     oClass isPointers ifTrue:[
                         1 to:owner basicSize do:[:i |
-                            (owner basicAt:i) == inspectedObject ifTrue:[
+                            (owner basicAt:i) == object ifTrue:[
                                  set add:i
                             ]
                         ]
@@ -1309,7 +1307,7 @@
         idx := idx - 1.
     ].
 
-    cls := inspectedObject class.
+    cls := object class.
     baseCls := self baseInspectedObjectClass.
 
     nNamedInstvarsShown := cls instSize.
@@ -1341,11 +1339,11 @@
 
     |derivedFieldList namedFieldList fieldList cls indexedList extraNamedFieldList|
 
-    inspectedObject isNil ifTrue:[
+    object isNil ifTrue:[
         ^ self hasSelfEntry ifFalse:[ #() ] ifTrue:[ #('-self') ]
     ].
 
-    cls := inspectedObject class.
+    cls := object class.
 
     self topView withWaitCursorDo:[
         namedFieldList := self namedFieldList.
@@ -1363,7 +1361,7 @@
                 derivedFieldList add:'-' , 'identityHash' allItalic.
 
                 cls hasImmediateInstances ifFalse:[
-                    inspectedObject dependents notEmptyOrNil ifTrue:[
+                    object dependents notEmptyOrNil ifTrue:[
                         derivedFieldList add:'-' , 'dependents' allItalic.
                     ].
                 ].
@@ -1403,11 +1401,11 @@
 
     | n cls|
 
-    cls := inspectedObject class.
+    cls := object class.
 
     cls isVariable ifFalse:[^ nil ].
 
-    n := inspectedObject basicSize.
+    n := object basicSize.
     (n > nShown) ifTrue:[
         n := nShown.
         hasMore := true.
@@ -1416,6 +1414,28 @@
     ^ (1 to:n)
 !
 
+indexOfFirstNamedInstvarInList
+    "helper - return the index for the first named instVar;
+     nil, if self or a keyed instvar is selected."
+
+    |firstRealIndex|
+
+    firstRealIndex := 1.
+    self hasSelfEntry ifTrue:[
+        firstRealIndex := 2.
+    ].
+
+    [
+        |line|
+
+        line := listView at:firstRealIndex. 
+        (line startsWith:'-') and:[line size < 2 or:[line second isDigit not]]
+    ] whileTrue:[
+        firstRealIndex := firstRealIndex + 1.
+    ].
+    ^ firstRealIndex
+!
+
 indexedFieldList 
     "return a list of indexed-variable names to show in the selectionList.
      Set hasMore to true, if a '...' entry should be added."
@@ -1428,19 +1448,19 @@
 !
 
 indexedValueAtIndex:idx
-    ^ inspectedObject basicAt:idx
+    ^ object basicAt:idx
 !
 
 indexedValueAtIndex:idx put:newValue
-    inspectedObject basicAt:idx put:newValue
+    object basicAt:idx put:newValue
 !
 
 indexedValueAtKey:key
     "/ kludge
-    inspectedObject isLimitedPrecisionReal ifTrue:[
-        ^ inspectedObject basicAt:key
+    object isLimitedPrecisionReal ifTrue:[
+        ^ object basicAt:key
     ].
-    ^ inspectedObject at:key
+    ^ object at:key
 !
 
 instVarIndexForLine:lineNr
@@ -1467,7 +1487,7 @@
         idx := idx - 1.
     ].
 
-    cls := inspectedObject class.
+    cls := object class.
     baseCls := self baseInspectedObjectClass.
 
     nNamedInstvarsShown := cls instSize.
@@ -1511,7 +1531,7 @@
         idx := idx - 1.
     ].
 
-    cls := inspectedObject class.
+    cls := object class.
     baseCls := self baseInspectedObjectClass.
 
     nNamedInstvarsShown := cls instSize.
@@ -1530,12 +1550,20 @@
     "Modified: / 04-08-2006 / 11:45:42 / cg"
 !
 
+namedFieldAt:idx
+    ^ object instVarAt:idx
+!
+
+namedFieldAt:idx put:newValue
+    ^ object instVarAt:idx put:newValue
+!
+
 namedFieldList 
     "return a list of instVar names to show in the selectionList."
 
     |aList cls baseCls|
 
-    cls := inspectedObject class.
+    cls := object class.
     baseCls := self baseInspectedObjectClass.
 
     aList := OrderedCollection new.
@@ -1559,7 +1587,7 @@
     acceptAction := [:theText | self doAccept:theText asString].
 
     (selectionIndex isNil 
-    or:[ inspectedObject class hasImmediateInstances])
+    or:[ object class hasImmediateInstances])
     ifTrue:[
         acceptAction := nil.
     ] ifFalse:[
@@ -1592,12 +1620,12 @@
         doItAction:[:theCode |
             |evaluator|
 
-            (evaluator := inspectedObject class evaluatorClass)
+            (evaluator := object class evaluatorClass)
             notNil ifTrue:[
                 evaluator
                     evaluate:theCode 
                     in:nil 
-                    receiver:inspectedObject 
+                    receiver:object 
                     notifying:workspace 
                     logged:true 
                     ifFail:nil
@@ -1606,7 +1634,7 @@
             ]
         ].
 
-    inspectedObject class evaluatorClass isNil ifTrue:[
+    object class evaluatorClass isNil ifTrue:[
         workspace doItAction:nil.
         workspace acceptAction:nil.
     ]
@@ -1624,7 +1652,7 @@
     hasMore ifTrue:[
         nShown := nShown * 2.
         "/ force update (which is otherwise ignored)
-        o := inspectedObject.
+        o := object.
         inspectedObject := object := nil.
         self inspect:o
     ]
@@ -1635,7 +1663,7 @@
 stringWithAllIndexedVarValues
     |nIdx s names maxLen varString padLeft|
 
-    nIdx := inspectedObject size.
+    nIdx := object size.
 
     s := CharacterWriteStream on:''.
     names := self indexList.
@@ -1673,12 +1701,12 @@
     |s names maxLen varString|
 
     s := CharacterWriteStream on:''.
-    names := inspectedObject class allInstVarNames.
+    names := object class allInstVarNames.
     maxLen := (names collect:[:eachName | eachName size]) max.
     names keysAndValuesDo:[:eachInstVarIndex :eachInstVarName |
         s nextPutAll:((eachInstVarName , ' ') paddedTo:maxLen+1 with:$.).
         s nextPutAll:' : '.
-        varString := self basicDisplayStringForValue:(inspectedObject instVarAt:eachInstVarIndex).
+        varString := self basicDisplayStringForValue:(object instVarAt:eachInstVarIndex).
         (varString includes:Character cr) ifTrue:[
             varString := varString copyTo:(varString indexOf:Character cr)-1.
             varString := varString , '...'.
@@ -1693,7 +1721,7 @@
     |cls s messages |
 
     s := CharacterWriteStream on:''.
-    cls := inspectedObject class.
+    cls := object class.
     which == #local ifTrue:[
         messages := cls selectors.
     ] ifFalse:[
@@ -1718,7 +1746,7 @@
 
     (self hasSelfEntry
     and:[lineNr == 1 or:[lineNr isNil]]) ifTrue:[
-        ^ inspectedObject
+        ^ object
     ].
 
     ((l := listView at:lineNr) startsWith:$-) ifTrue:[
@@ -1731,7 +1759,7 @@
     idx := self instVarIndexForLine:lineNr.
     idx notNil ifTrue:[
         BreakPointInterrupt catch:[
-            ^ inspectedObject instVarAt:idx
+            ^ self namedFieldAt:idx
         ]
     ].
 
@@ -1764,21 +1792,23 @@
 
     idx := self instVarIndexForLine:selectionIndex.
     idx notNil ifTrue:[
-        inspectedObject instVarAt:idx put:newValue.
-    ] ifFalse:[
-        idx := self keyIndexForLine:selectionIndex.
-        idx notNil ifTrue:[
-            self indexedValueAtIndex:idx put:newValue.
-        ] ifFalse:[
-            ^ self "/ self selected - dont store
-        ]
+        self namedFieldAt:idx put:newValue.
+        ^ self.
     ].
+
+    idx := self keyIndexForLine:selectionIndex.
+    idx notNil ifTrue:[
+        self indexedValueAtIndex:idx put:newValue.
+        ^ self
+    ].
+
+    ^ self "/ self selected - dont store
 !
 
 valueForSpecialLine:line
-    |idx fieldEntry val extraAttributes|
-
-    extraAttributes := inspectedObject inspectorExtraAttributes.
+    |idx fieldEntry extraAttributes|
+
+    extraAttributes := object inspectorExtraAttributes.
     (extraAttributes notNil and:[ extraAttributes includesKey:line ]) ifTrue:[
         ^ (extraAttributes at:line) value 
     ].
@@ -1800,28 +1830,28 @@
     ].
 
     (line startsWith:'-self') ifTrue:[
-        ^ inspectedObject
+        ^ object
     ].
     (line startsWith:'-hash') ifTrue:[
-        ^ inspectedObject hash
+        ^ object hash
     ].
     (line startsWith:'-identityHash') ifTrue:[
-        ^ inspectedObject identityHash
+        ^ object identityHash
     ].
     (line startsWith:'-dependents') ifTrue:[
-        ^ inspectedObject dependents
+        ^ object dependents
     ].
     (line startsWith:'-all') ifTrue:[
-        ^ inspectedObject
+        ^ object
     ].
     (line startsWith:'-local messages') ifTrue:[
-        ^ inspectedObject
+        ^ object
     ].
     (line startsWith:'-inherited messages') ifTrue:[
-        ^ inspectedObject
+        ^ object
     ].
     (line startsWith:'-all messages') ifTrue:[
-        ^ inspectedObject
+        ^ object
     ].
 
     self error:'unknown special line'.
@@ -1837,7 +1867,7 @@
 !
 
 compilerClass
-    ^ inspectedObject class compilerClass
+    ^ object class compilerClass
 !
 
 dereferenceValueHolders
@@ -1996,7 +2026,7 @@
     selectionIndex notNil ifTrue:[
         sel := listView at:selectionIndex.
 
-        extraAttributes := inspectedObject inspectorExtraAttributes.
+        extraAttributes := object inspectorExtraAttributes.
         (extraAttributes notNil and:[extraAttributes includesKey:sel]) ifTrue:[
             ^ (extraAttributes at:sel) value printString
         ].
@@ -2081,9 +2111,9 @@
     Error handle:[:ex |
         workspace flash
     ] do:[
-        newValue := inspectedObject class evaluatorClass 
+        newValue := object class evaluatorClass 
                        evaluate:theText
-                       receiver:inspectedObject 
+                       receiver:object 
                        notifying:workspace.
 
         self dereferenceValueHolders ifTrue:[
@@ -2219,9 +2249,9 @@
 !InspectorView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/InspectorView.st,v 1.205 2010-02-01 14:58:05 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/InspectorView.st,v 1.206 2010-02-06 17:57:29 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libtool/InspectorView.st,v 1.205 2010-02-01 14:58:05 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/InspectorView.st,v 1.206 2010-02-06 17:57:29 cg Exp $'
 ! !