checkin from browser
authorca
Wed, 15 Jan 1997 14:32:46 +0100
changeset 38 7b75ce74d9e1
parent 37 758be6e05f1d
child 39 03af455029eb
checkin from browser
InspectorList.st
NewInspectorList.st
--- a/InspectorList.st	Mon Jan 13 18:05:11 1997 +0100
+++ b/InspectorList.st	Wed Jan 15 14:32:46 1997 +0100
@@ -13,7 +13,43 @@
 for:anObject
     "create a new list for an instance
     "
-    ^ self basicNew for:anObject
+    ^ self new inspect:anObject
+
+
+!
+
+new
+    "create a new instance and set the inspected object to nil
+    "
+    ^ self basicNew initialize.
+
+! !
+
+!InspectorList class methodsFor:'helpers'!
+
+asString:aCollection
+    "converts any collection to a string seperated by spaces. If
+     the collection is empty or nil, nil is returned otherwise a
+     string.
+    "
+    |string|
+
+    aCollection isCollection ifTrue:[
+        aCollection isString ifTrue:[
+            string := aCollection
+        ] ifFalse:[
+            string := aCollection asStringWith:Character space
+                                          from:1 to:(aCollection size)
+                                  compressTabs:true 
+                                         final:nil
+        ].
+        string := string withoutSeparators.
+
+        string notEmpty ifTrue:[
+            ^ string
+        ]
+    ].
+    ^ nil
 
 
 ! !
@@ -21,7 +57,7 @@
 !InspectorList class methodsFor:'testing'!
 
 isDirectory:anInstance
-    "returns true if the class is a directory
+    "returns true if the instance is a directory
     "
     |cls|
 
@@ -43,18 +79,27 @@
     ^ false
 
 
+!
+
+isTraceable:anInstance
+    "returns true if the instance could be traced or traped
+    "
+    |cls|
+
+    anInstance notNil ifTrue:[
+        cls := anInstance class.
+
+      ^ (     cls ~~ True
+         and:[cls ~~ False
+         and:[cls ~~ SmallInteger]]
+        )
+    ].
+    ^ false.
+
 ! !
 
 !InspectorList methodsFor:'accessing'!
 
-includesSelf
-    "returns true if 'self' is included in the list
-    "
-    ^ (self instanceTypeAt:1) == #self
-
-
-!
-
 includesSelf:aBoolean
     "includes 'self' dependant on the boolean
     "
@@ -63,8 +108,9 @@
             instanceNames addFirst:'self'.
             instanceTypes addFirst:#self.
 
-            selection isNil ifTrue:[selection := 1]
-                           ifFalse:[selection := selection + 1]
+            selection notNil ifTrue:[selection := selection + 1]
+                            ifFalse:[selection := 1]
+
         ] ifFalse:[
             instanceNames removeFirst.
             instanceTypes removeFirst.
@@ -80,11 +126,39 @@
 
 !
 
+list
+    "returns self
+    "
+    ^ self
+!
+
 size
-    "returns current list size
+    "returns size of list
     "
     ^ instanceNames size
 
+!
+
+update
+    "update list contents
+    "
+    |start stop size|
+
+    inspectedObject isVariable ifTrue:[
+        start := instanceNames findFirst:[:el|(el at:1) isDigit].
+        stop  := instanceTypes size.
+
+        start == 0 ifTrue:[
+            size := stop + 10.  "must be > 1: force a resize the first time"   
+        ] ifFalse:[
+            instanceTypes last ~~ #grow ifTrue:[size := stop]
+                                       ifFalse:[size := stop-1].
+
+            instanceTypes removeFromIndex:start toIndex:stop.
+            instanceNames removeFromIndex:start toIndex:stop.
+        ].
+        self resizeTo:size.
+    ]
 ! !
 
 !InspectorList methodsFor:'accessing contents'!
@@ -97,25 +171,6 @@
 
 !
 
-instanceNameAt:anIndex
-    "returns the name assigned to the index
-    "
-    |idx nm|
-
-    (anIndex notNil and:[anIndex <= instanceTypes size]) ifTrue:[
-        nm := instanceNames at:anIndex.
-
-        (nm at:1) isDigit ifFalse:[
-            ^ nm
-        ].
-        idx := Number readFrom:nm onError:0.
-        ^ '[', idx printString, ']'.
-    ].
-    ^ nil
-
-
-!
-
 instanceNames
     "returns list of instance names
     "
@@ -125,18 +180,17 @@
 !
 
 instanceTypeAt:anIndex
-    "returns type assigned to the list entry (#directory #normal #self)
+    "returns type assigned to the list entry (#directory #normal #self #grow)
+     In case of an invalid index nil is returned.
     "
-    (anIndex notNil and:[anIndex <= instanceTypes size]) ifTrue:[
-        ^ instanceTypes at:anIndex
-    ].
-    ^ nil
+    (anIndex isNil or:[anIndex > instanceTypes size]) ifFalse:[^ instanceTypes at:anIndex]
+                                                       ifTrue:[^ nil].
 
 
 !
 
 instanceTypes
-    "returns list of types (#directory #normal #self)
+    "returns list of types (#directory #normal #self #grow)
     "
     ^ instanceTypes
 
@@ -144,11 +198,12 @@
 !
 
 instanceVarAt:anIndex
-    "returns the instnace variable assigned to the index
+    "returns the instnace variable assigned to the index or 
+     nil in case of an invalid index.
     "
     |idx nm|
 
-    (anIndex notNil and:[anIndex <= instanceTypes size]) ifTrue:[
+    (anIndex isNil or:[anIndex > instanceTypes size]) ifFalse:[
         nm := instanceNames at:anIndex.
 
         (nm at:1) isDigit ifFalse:[
@@ -165,149 +220,51 @@
 
 ! !
 
-!InspectorList methodsFor:'actions'!
-
-accept:aText notifying:aView
-    "on error #Error is returned otherwise the inspected object instance
-    "
-    |txt slNr value|
-
-    (selection isNil or:[(txt := self textToString:aText) isNil]) ifTrue:[
-        ^ #Error
-    ].
-
-    self includesSelf ifFalse:[slNr := selection]
-                       ifTrue:[slNr := selection -1].
-
-    value := inspectedObject class evaluatorClass 
-               evaluate:txt
-               receiver:inspectedObject 
-              notifying:aView.
-
-    slNr ~~ 0 ifTrue:[
-        (inspectedObject class isVariable) ifFalse:[
-            inspectedObject instVarAt:slNr put:value
-        ] ifTrue:[
-            slNr <= (inspectedObject class instSize) ifTrue:[
-                inspectedObject instVarAt:slNr put:value
-            ] ifFalse:[
-                slNr := slNr - inspectedObject class instSize.
-                inspectedObject basicAt:slNr put:value
-            ]
-        ]
-    ].
-    inspectedObject changed.
-    self update.
-  ^ inspectedObject
-
-
-!
-
-doIt:aCode notifying:aView
-    "on success the value returned from parser is returned otherwise #Error
-    "
-    |code result evaluator selInstVar state|
-
-    (selection isNil or:[(code := self textToString:aCode) isNil]) ifFalse:[
-        selInstVar := self selectedInstanceVar.
-        evaluator  := selInstVar class evaluatorClass.
-        state      := true.
-
-        evaluator notNil ifTrue:[
-            result := evaluator evaluate:code 
-                                      in:nil 
-                                receiver:selInstVar 
-                               notifying:aView 
-                                  logged:true 
-                                  ifFail:[state := false].
-
-            state ifTrue:[
-                self update.
-              ^ result
-            ]
-        ]
-    ].
-    ^ #Error.
-
-
-! !
-
 !InspectorList methodsFor:'initialization'!
 
-for:anObject
-    "setup a new instance
+initialize
+    "initialize instance attributes
     "
-    |varNamesSize|
-
-    inspectedObject := anObject.
-    selection       := nil.
-
-    (self class isDirectory:inspectedObject) ifTrue:[
-        instanceNames := inspectedObject class allInstVarNames.
-        varNamesSize  := instanceNames size.
-        instanceTypes := OrderedCollection new:varNamesSize.
+    super initialize.
 
-        1 to:varNamesSize do:[:i|
-            (self class isDirectory:(inspectedObject instVarAt:i)) ifTrue:[
-                instanceTypes add:#directory
-            ] ifFalse:[
-                instanceTypes add:#normal
-            ]
-        ]
-    ] ifFalse:[
-        instanceNames := OrderedCollection new.
-        instanceTypes := OrderedCollection new.
-    ].
-    self update.
+    instanceNames := OrderedCollection new.
+    instanceTypes := OrderedCollection new.
+
 ! !
 
 !InspectorList methodsFor:'private'!
 
-lastVariableId
-    "returns last variable id or nil if not growable
+resizeTo:aNumber
+    "resize list to minimum aNumber
     "
-    |lstId bscSz|
+    |lstVarId basicSize newLastId obj instSize|
 
     (inspectedObject isVariable and:[self class isDirectory:inspectedObject]) ifFalse:[
-        ^ nil
-    ].
-
-    bscSz := inspectedObject class instSize.
-
-    self includesSelf ifTrue:[
-        bscSz := bscSz + 1.
-    ].
-    lstId := instanceTypes size - bscSz.
-
-    (lstId ~~ 0 and:[instanceTypes last == #grow]) ifTrue:[^ lstId-1]
-                                                  ifFalse:[^ lstId].
-!
-
-resizeVariableList:toNumber
-    "resize variable list
-    "
-    |lstVarId basicSize newLastId obj|
-
-    (lstVarId := self lastVariableId) isNil ifTrue:[
         ^ self
     ].
 
-    basicSize := inspectedObject basicSize.
+    instanceTypes size == 0 ifTrue:[
+        lstVarId := 0
+    ] ifFalse:[
+        instSize := inspectedObject class instSize.
 
-    (toNumber <= lstVarId or:[basicSize == lstVarId]) ifTrue:[
-        ^ self
-    ].
-    newLastId := (toNumber + 49) roundTo:100.
-
-    newLastId > basicSize ifTrue:[
-        newLastId := basicSize
-    ].
-
-    lstVarId ~~ 0 ifTrue:[
+        instanceTypes first == #self ifTrue:[
+            instSize := instSize + 1
+        ].
         instanceTypes last == #grow ifTrue:[
             instanceNames removeLast.       " ..    "
             instanceTypes removeLast.       " #grow "
-        ]
+        ].
+        lstVarId := instanceTypes size - instSize.
+    ].
+
+    (basicSize := inspectedObject basicSize) == lstVarId ifTrue:[
+        ^ self
+    ].
+    newLastId := (1 bitShift:((aNumber-1) highBit)) max:128.
+
+    (newLastId + 64) > basicSize ifTrue:[
+        newLastId := basicSize
     ].
 
     [lstVarId ~~ newLastId] whileTrue:[
@@ -324,65 +281,13 @@
         instanceNames add:'..'.
         instanceTypes add:#grow
     ].
-
-
-!
-
-textToString:aText
-    "converts a text to a string
-    "
-    |s|
-
-    aText isString ifTrue:[
-        s := aText string
-    ] ifFalse:[
-        aText isCollection ifTrue:[
-            s := ''.
-            aText do:[:el|el notNil ifTrue:[s := s, el string]].
-        ]
-    ].
-
-    s notNil ifTrue:[
-        (s := s withoutSeparators) notEmpty ifTrue:[
-            ^ s
-        ]
-    ].
-    ^ nil.
-
-
-!
-
-update
-    "update contents
-    "
-    |delNr lstVarId|
-
-    (lstVarId := self lastVariableId) isNil ifFalse:[
-        lstVarId == 0 ifTrue:[
-            lstVarId := 100
-        ] ifFalse:[
-            instanceTypes last == #grow ifTrue:[delNr := lstVarId+1]
-                                       ifFalse:[delNr := lstVarId].
-
-            instanceTypes removeLast:delNr.     
-            instanceNames removeLast:delNr.
-        ].
-        self resizeVariableList:lstVarId.
-    ]
 ! !
 
 !InspectorList methodsFor:'selections'!
 
-selectedInstanceName
-    "returns name of current selection or nil
-    "
-    ^ self instanceNameAt:selection
-
-
-!
-
 selectedInstanceType
-    "returns type of current selection or nil
+    "returns type assigned to the selected list entry (#directory #normal #self #grow).
+     In case of no selection nil is returned.
     "
     ^ self instanceTypeAt:selection
 
@@ -405,29 +310,149 @@
 
 !
 
-selection:aNrOrNil
-    "change current selection to a number or nil; may grow a variable list
+setSelection:aNrOrNil
+    "change current selection to a number or nil; may resize the lists
+    "
+    selection := aNrOrNil.
+
+    (selection isNil or:[instanceTypes size > selection]) ifFalse:[
+        self resizeTo:selection.
+
+        selection > instanceTypes size ifTrue:[
+            selection := nil
+        ]
+    ]    
+! !
+
+!InspectorList methodsFor:'testing'!
+
+includesSelf
+    "returns true if 'self' is included in the list
+    "
+    ^ (instanceTypes notEmpty and:[instanceTypes first == #self])
+
+
+!
+
+isEmpty
+    "returns true if the list is empty
     "
-    |rsz|
+    ^ instanceNames isEmpty
+
+!
+
+notEmpty
+    "returns true if the list is not empty
+    "
+    ^ instanceNames notEmpty
+
+! !
+
+!InspectorList methodsFor:'user interaction'!
+
+accept:aText notifying:aView
+    "evaluating aText on the selected instance var; if an error occurs #Error
+     is returned otherwise the inspected object instance. On success the list
+     will be updated.
+    "
+    |text slNr value|
+
+    selection notNil ifTrue:[
+        text := self class asString:aText.
+
+        text notNil ifTrue:[
+            self includesSelf ifFalse:[slNr := selection]
+                               ifTrue:[slNr := selection-1].
+
+            value := inspectedObject class evaluatorClass 
+                       evaluate:text
+                       receiver:inspectedObject 
+                      notifying:aView.
 
-    aNrOrNil isNil ifTrue:[
-        self includesSelf ifTrue:[selection := 1]
-                         ifFalse:[selection := nil]
-    ] ifFalse:[
-        aNrOrNil >= instanceNames size ifTrue:[
-            (rsz := self lastVariableId) notNil ifTrue:[
-                rsz := rsz * 2.
+            slNr ~~ 0 ifTrue:[
+                (inspectedObject class isVariable) ifFalse:[
+                    inspectedObject instVarAt:slNr put:value
+                ] ifTrue:[
+                    slNr <= (inspectedObject class instSize) ifTrue:[
+                        inspectedObject instVarAt:slNr put:value
+                    ] ifFalse:[
+                        slNr := slNr - inspectedObject class instSize.
+                        inspectedObject basicAt:slNr put:value
+                    ]
+                ]
+            ].
+            inspectedObject changed.
+            self update.
+          ^ inspectedObject
+        ]
+    ].
+    ^ #Error
+!
+
+doIt:aCode notifying:aView
+    "evaluating aCode on the selected instance var; if an error occurs #Error
+     is returned otherwise the result returned from the evaluator. On success
+     the list will be updated.
+    "
+    |successFg result evaluator selInstVar code|
+
+    selInstVar := self selectedInstanceVar.
+
+    selInstVar notNil ifTrue:[
+        code := self class asString:aCode.
+
+        code notNil ifTrue:[
+            evaluator := selInstVar class evaluatorClass.
+            successFg := true.
 
-                rsz < aNrOrNil ifTrue:[
-                    rsz := aNrOrNil
-                ].
-                self resizeVariableList:rsz
+            evaluator notNil ifTrue:[
+                result := evaluator evaluate:code 
+                                          in:nil 
+                                    receiver:selInstVar 
+                                   notifying:aView 
+                                      logged:true 
+                                      ifFail:[successFg := false].
+
+                successFg ifTrue:[
+                    self update. 
+                  ^ result 
+                ]
             ]
-        ].
-        aNrOrNil > instanceNames size ifFalse:[selection := aNrOrNil]
-                                       ifTrue:[selection := nil]
-    ]
+        ]
+    ].
+    ^ #Error.
+
+
+!
+
+inspect:anObject
+    "inspect a new instance; update contents
+    "
+    |varNamesSize|
+
+    selection := nil.
+
+    anObject == inspectedObject ifFalse:[
+        inspectedObject := anObject.
 
+        (self class isDirectory:inspectedObject) ifFalse:[
+            instanceNames := OrderedCollection new.
+            instanceTypes := OrderedCollection new.
+        ] ifTrue:[    
+            instanceNames := inspectedObject class allInstVarNames.
+            varNamesSize  := instanceNames size.
+            instanceTypes := OrderedCollection new:varNamesSize.
+
+            1 to:varNamesSize do:[:i|
+                (self class isDirectory:(inspectedObject instVarAt:i)) ifTrue:[
+                    instanceTypes add:#directory
+                ] ifFalse:[
+                    instanceTypes add:#normal
+                ]
+            ].
+        ]
+    ].
+    self update
 ! !
 
 !InspectorList class methodsFor:'documentation'!
--- a/NewInspectorList.st	Mon Jan 13 18:05:11 1997 +0100
+++ b/NewInspectorList.st	Wed Jan 15 14:32:46 1997 +0100
@@ -13,7 +13,43 @@
 for:anObject
     "create a new list for an instance
     "
-    ^ self basicNew for:anObject
+    ^ self new inspect:anObject
+
+
+!
+
+new
+    "create a new instance and set the inspected object to nil
+    "
+    ^ self basicNew initialize.
+
+! !
+
+!InspectorList class methodsFor:'helpers'!
+
+asString:aCollection
+    "converts any collection to a string seperated by spaces. If
+     the collection is empty or nil, nil is returned otherwise a
+     string.
+    "
+    |string|
+
+    aCollection isCollection ifTrue:[
+        aCollection isString ifTrue:[
+            string := aCollection
+        ] ifFalse:[
+            string := aCollection asStringWith:Character space
+                                          from:1 to:(aCollection size)
+                                  compressTabs:true 
+                                         final:nil
+        ].
+        string := string withoutSeparators.
+
+        string notEmpty ifTrue:[
+            ^ string
+        ]
+    ].
+    ^ nil
 
 
 ! !
@@ -21,7 +57,7 @@
 !InspectorList class methodsFor:'testing'!
 
 isDirectory:anInstance
-    "returns true if the class is a directory
+    "returns true if the instance is a directory
     "
     |cls|
 
@@ -43,18 +79,27 @@
     ^ false
 
 
+!
+
+isTraceable:anInstance
+    "returns true if the instance could be traced or traped
+    "
+    |cls|
+
+    anInstance notNil ifTrue:[
+        cls := anInstance class.
+
+      ^ (     cls ~~ True
+         and:[cls ~~ False
+         and:[cls ~~ SmallInteger]]
+        )
+    ].
+    ^ false.
+
 ! !
 
 !InspectorList methodsFor:'accessing'!
 
-includesSelf
-    "returns true if 'self' is included in the list
-    "
-    ^ (self instanceTypeAt:1) == #self
-
-
-!
-
 includesSelf:aBoolean
     "includes 'self' dependant on the boolean
     "
@@ -63,8 +108,9 @@
             instanceNames addFirst:'self'.
             instanceTypes addFirst:#self.
 
-            selection isNil ifTrue:[selection := 1]
-                           ifFalse:[selection := selection + 1]
+            selection notNil ifTrue:[selection := selection + 1]
+                            ifFalse:[selection := 1]
+
         ] ifFalse:[
             instanceNames removeFirst.
             instanceTypes removeFirst.
@@ -80,11 +126,39 @@
 
 !
 
+list
+    "returns self
+    "
+    ^ self
+!
+
 size
-    "returns current list size
+    "returns size of list
     "
     ^ instanceNames size
 
+!
+
+update
+    "update list contents
+    "
+    |start stop size|
+
+    inspectedObject isVariable ifTrue:[
+        start := instanceNames findFirst:[:el|(el at:1) isDigit].
+        stop  := instanceTypes size.
+
+        start == 0 ifTrue:[
+            size := stop + 10.  "must be > 1: force a resize the first time"   
+        ] ifFalse:[
+            instanceTypes last ~~ #grow ifTrue:[size := stop]
+                                       ifFalse:[size := stop-1].
+
+            instanceTypes removeFromIndex:start toIndex:stop.
+            instanceNames removeFromIndex:start toIndex:stop.
+        ].
+        self resizeTo:size.
+    ]
 ! !
 
 !InspectorList methodsFor:'accessing contents'!
@@ -97,25 +171,6 @@
 
 !
 
-instanceNameAt:anIndex
-    "returns the name assigned to the index
-    "
-    |idx nm|
-
-    (anIndex notNil and:[anIndex <= instanceTypes size]) ifTrue:[
-        nm := instanceNames at:anIndex.
-
-        (nm at:1) isDigit ifFalse:[
-            ^ nm
-        ].
-        idx := Number readFrom:nm onError:0.
-        ^ '[', idx printString, ']'.
-    ].
-    ^ nil
-
-
-!
-
 instanceNames
     "returns list of instance names
     "
@@ -125,18 +180,17 @@
 !
 
 instanceTypeAt:anIndex
-    "returns type assigned to the list entry (#directory #normal #self)
+    "returns type assigned to the list entry (#directory #normal #self #grow)
+     In case of an invalid index nil is returned.
     "
-    (anIndex notNil and:[anIndex <= instanceTypes size]) ifTrue:[
-        ^ instanceTypes at:anIndex
-    ].
-    ^ nil
+    (anIndex isNil or:[anIndex > instanceTypes size]) ifFalse:[^ instanceTypes at:anIndex]
+                                                       ifTrue:[^ nil].
 
 
 !
 
 instanceTypes
-    "returns list of types (#directory #normal #self)
+    "returns list of types (#directory #normal #self #grow)
     "
     ^ instanceTypes
 
@@ -144,11 +198,12 @@
 !
 
 instanceVarAt:anIndex
-    "returns the instnace variable assigned to the index
+    "returns the instnace variable assigned to the index or 
+     nil in case of an invalid index.
     "
     |idx nm|
 
-    (anIndex notNil and:[anIndex <= instanceTypes size]) ifTrue:[
+    (anIndex isNil or:[anIndex > instanceTypes size]) ifFalse:[
         nm := instanceNames at:anIndex.
 
         (nm at:1) isDigit ifFalse:[
@@ -165,149 +220,51 @@
 
 ! !
 
-!InspectorList methodsFor:'actions'!
-
-accept:aText notifying:aView
-    "on error #Error is returned otherwise the inspected object instance
-    "
-    |txt slNr value|
-
-    (selection isNil or:[(txt := self textToString:aText) isNil]) ifTrue:[
-        ^ #Error
-    ].
-
-    self includesSelf ifFalse:[slNr := selection]
-                       ifTrue:[slNr := selection -1].
-
-    value := inspectedObject class evaluatorClass 
-               evaluate:txt
-               receiver:inspectedObject 
-              notifying:aView.
-
-    slNr ~~ 0 ifTrue:[
-        (inspectedObject class isVariable) ifFalse:[
-            inspectedObject instVarAt:slNr put:value
-        ] ifTrue:[
-            slNr <= (inspectedObject class instSize) ifTrue:[
-                inspectedObject instVarAt:slNr put:value
-            ] ifFalse:[
-                slNr := slNr - inspectedObject class instSize.
-                inspectedObject basicAt:slNr put:value
-            ]
-        ]
-    ].
-    inspectedObject changed.
-    self update.
-  ^ inspectedObject
-
-
-!
-
-doIt:aCode notifying:aView
-    "on success the value returned from parser is returned otherwise #Error
-    "
-    |code result evaluator selInstVar state|
-
-    (selection isNil or:[(code := self textToString:aCode) isNil]) ifFalse:[
-        selInstVar := self selectedInstanceVar.
-        evaluator  := selInstVar class evaluatorClass.
-        state      := true.
-
-        evaluator notNil ifTrue:[
-            result := evaluator evaluate:code 
-                                      in:nil 
-                                receiver:selInstVar 
-                               notifying:aView 
-                                  logged:true 
-                                  ifFail:[state := false].
-
-            state ifTrue:[
-                self update.
-              ^ result
-            ]
-        ]
-    ].
-    ^ #Error.
-
-
-! !
-
 !InspectorList methodsFor:'initialization'!
 
-for:anObject
-    "setup a new instance
+initialize
+    "initialize instance attributes
     "
-    |varNamesSize|
-
-    inspectedObject := anObject.
-    selection       := nil.
-
-    (self class isDirectory:inspectedObject) ifTrue:[
-        instanceNames := inspectedObject class allInstVarNames.
-        varNamesSize  := instanceNames size.
-        instanceTypes := OrderedCollection new:varNamesSize.
+    super initialize.
 
-        1 to:varNamesSize do:[:i|
-            (self class isDirectory:(inspectedObject instVarAt:i)) ifTrue:[
-                instanceTypes add:#directory
-            ] ifFalse:[
-                instanceTypes add:#normal
-            ]
-        ]
-    ] ifFalse:[
-        instanceNames := OrderedCollection new.
-        instanceTypes := OrderedCollection new.
-    ].
-    self update.
+    instanceNames := OrderedCollection new.
+    instanceTypes := OrderedCollection new.
+
 ! !
 
 !InspectorList methodsFor:'private'!
 
-lastVariableId
-    "returns last variable id or nil if not growable
+resizeTo:aNumber
+    "resize list to minimum aNumber
     "
-    |lstId bscSz|
+    |lstVarId basicSize newLastId obj instSize|
 
     (inspectedObject isVariable and:[self class isDirectory:inspectedObject]) ifFalse:[
-        ^ nil
-    ].
-
-    bscSz := inspectedObject class instSize.
-
-    self includesSelf ifTrue:[
-        bscSz := bscSz + 1.
-    ].
-    lstId := instanceTypes size - bscSz.
-
-    (lstId ~~ 0 and:[instanceTypes last == #grow]) ifTrue:[^ lstId-1]
-                                                  ifFalse:[^ lstId].
-!
-
-resizeVariableList:toNumber
-    "resize variable list
-    "
-    |lstVarId basicSize newLastId obj|
-
-    (lstVarId := self lastVariableId) isNil ifTrue:[
         ^ self
     ].
 
-    basicSize := inspectedObject basicSize.
+    instanceTypes size == 0 ifTrue:[
+        lstVarId := 0
+    ] ifFalse:[
+        instSize := inspectedObject class instSize.
 
-    (toNumber <= lstVarId or:[basicSize == lstVarId]) ifTrue:[
-        ^ self
-    ].
-    newLastId := (toNumber + 49) roundTo:100.
-
-    newLastId > basicSize ifTrue:[
-        newLastId := basicSize
-    ].
-
-    lstVarId ~~ 0 ifTrue:[
+        instanceTypes first == #self ifTrue:[
+            instSize := instSize + 1
+        ].
         instanceTypes last == #grow ifTrue:[
             instanceNames removeLast.       " ..    "
             instanceTypes removeLast.       " #grow "
-        ]
+        ].
+        lstVarId := instanceTypes size - instSize.
+    ].
+
+    (basicSize := inspectedObject basicSize) == lstVarId ifTrue:[
+        ^ self
+    ].
+    newLastId := (1 bitShift:((aNumber-1) highBit)) max:128.
+
+    (newLastId + 64) > basicSize ifTrue:[
+        newLastId := basicSize
     ].
 
     [lstVarId ~~ newLastId] whileTrue:[
@@ -324,65 +281,13 @@
         instanceNames add:'..'.
         instanceTypes add:#grow
     ].
-
-
-!
-
-textToString:aText
-    "converts a text to a string
-    "
-    |s|
-
-    aText isString ifTrue:[
-        s := aText string
-    ] ifFalse:[
-        aText isCollection ifTrue:[
-            s := ''.
-            aText do:[:el|el notNil ifTrue:[s := s, el string]].
-        ]
-    ].
-
-    s notNil ifTrue:[
-        (s := s withoutSeparators) notEmpty ifTrue:[
-            ^ s
-        ]
-    ].
-    ^ nil.
-
-
-!
-
-update
-    "update contents
-    "
-    |delNr lstVarId|
-
-    (lstVarId := self lastVariableId) isNil ifFalse:[
-        lstVarId == 0 ifTrue:[
-            lstVarId := 100
-        ] ifFalse:[
-            instanceTypes last == #grow ifTrue:[delNr := lstVarId+1]
-                                       ifFalse:[delNr := lstVarId].
-
-            instanceTypes removeLast:delNr.     
-            instanceNames removeLast:delNr.
-        ].
-        self resizeVariableList:lstVarId.
-    ]
 ! !
 
 !InspectorList methodsFor:'selections'!
 
-selectedInstanceName
-    "returns name of current selection or nil
-    "
-    ^ self instanceNameAt:selection
-
-
-!
-
 selectedInstanceType
-    "returns type of current selection or nil
+    "returns type assigned to the selected list entry (#directory #normal #self #grow).
+     In case of no selection nil is returned.
     "
     ^ self instanceTypeAt:selection
 
@@ -405,29 +310,149 @@
 
 !
 
-selection:aNrOrNil
-    "change current selection to a number or nil; may grow a variable list
+setSelection:aNrOrNil
+    "change current selection to a number or nil; may resize the lists
+    "
+    selection := aNrOrNil.
+
+    (selection isNil or:[instanceTypes size > selection]) ifFalse:[
+        self resizeTo:selection.
+
+        selection > instanceTypes size ifTrue:[
+            selection := nil
+        ]
+    ]    
+! !
+
+!InspectorList methodsFor:'testing'!
+
+includesSelf
+    "returns true if 'self' is included in the list
+    "
+    ^ (instanceTypes notEmpty and:[instanceTypes first == #self])
+
+
+!
+
+isEmpty
+    "returns true if the list is empty
     "
-    |rsz|
+    ^ instanceNames isEmpty
+
+!
+
+notEmpty
+    "returns true if the list is not empty
+    "
+    ^ instanceNames notEmpty
+
+! !
+
+!InspectorList methodsFor:'user interaction'!
+
+accept:aText notifying:aView
+    "evaluating aText on the selected instance var; if an error occurs #Error
+     is returned otherwise the inspected object instance. On success the list
+     will be updated.
+    "
+    |text slNr value|
+
+    selection notNil ifTrue:[
+        text := self class asString:aText.
+
+        text notNil ifTrue:[
+            self includesSelf ifFalse:[slNr := selection]
+                               ifTrue:[slNr := selection-1].
+
+            value := inspectedObject class evaluatorClass 
+                       evaluate:text
+                       receiver:inspectedObject 
+                      notifying:aView.
 
-    aNrOrNil isNil ifTrue:[
-        self includesSelf ifTrue:[selection := 1]
-                         ifFalse:[selection := nil]
-    ] ifFalse:[
-        aNrOrNil >= instanceNames size ifTrue:[
-            (rsz := self lastVariableId) notNil ifTrue:[
-                rsz := rsz * 2.
+            slNr ~~ 0 ifTrue:[
+                (inspectedObject class isVariable) ifFalse:[
+                    inspectedObject instVarAt:slNr put:value
+                ] ifTrue:[
+                    slNr <= (inspectedObject class instSize) ifTrue:[
+                        inspectedObject instVarAt:slNr put:value
+                    ] ifFalse:[
+                        slNr := slNr - inspectedObject class instSize.
+                        inspectedObject basicAt:slNr put:value
+                    ]
+                ]
+            ].
+            inspectedObject changed.
+            self update.
+          ^ inspectedObject
+        ]
+    ].
+    ^ #Error
+!
+
+doIt:aCode notifying:aView
+    "evaluating aCode on the selected instance var; if an error occurs #Error
+     is returned otherwise the result returned from the evaluator. On success
+     the list will be updated.
+    "
+    |successFg result evaluator selInstVar code|
+
+    selInstVar := self selectedInstanceVar.
+
+    selInstVar notNil ifTrue:[
+        code := self class asString:aCode.
+
+        code notNil ifTrue:[
+            evaluator := selInstVar class evaluatorClass.
+            successFg := true.
 
-                rsz < aNrOrNil ifTrue:[
-                    rsz := aNrOrNil
-                ].
-                self resizeVariableList:rsz
+            evaluator notNil ifTrue:[
+                result := evaluator evaluate:code 
+                                          in:nil 
+                                    receiver:selInstVar 
+                                   notifying:aView 
+                                      logged:true 
+                                      ifFail:[successFg := false].
+
+                successFg ifTrue:[
+                    self update. 
+                  ^ result 
+                ]
             ]
-        ].
-        aNrOrNil > instanceNames size ifFalse:[selection := aNrOrNil]
-                                       ifTrue:[selection := nil]
-    ]
+        ]
+    ].
+    ^ #Error.
+
+
+!
+
+inspect:anObject
+    "inspect a new instance; update contents
+    "
+    |varNamesSize|
+
+    selection := nil.
+
+    anObject == inspectedObject ifFalse:[
+        inspectedObject := anObject.
 
+        (self class isDirectory:inspectedObject) ifFalse:[
+            instanceNames := OrderedCollection new.
+            instanceTypes := OrderedCollection new.
+        ] ifTrue:[    
+            instanceNames := inspectedObject class allInstVarNames.
+            varNamesSize  := instanceNames size.
+            instanceTypes := OrderedCollection new:varNamesSize.
+
+            1 to:varNamesSize do:[:i|
+                (self class isDirectory:(inspectedObject instVarAt:i)) ifTrue:[
+                    instanceTypes add:#directory
+                ] ifFalse:[
+                    instanceTypes add:#normal
+                ]
+            ].
+        ]
+    ].
+    self update
 ! !
 
 !InspectorList class methodsFor:'documentation'!