*** empty log message ***
authorca
Wed, 15 Jan 1997 14:33:11 +0100
changeset 39 03af455029eb
parent 38 7b75ce74d9e1
child 40 03d7245cdc01
*** empty log message ***
InspectorListView.st
InspectorPanelView.st
InspectorView.st
NewInspectorListView.st
NewInspectorPanelView.st
NewInspectorView.st
--- a/InspectorListView.st	Wed Jan 15 14:32:46 1997 +0100
+++ b/InspectorListView.st	Wed Jan 15 14:33:11 1997 +0100
@@ -1,7 +1,7 @@
 "{ NameSpace: NewInspector }"
 
 SelectionInListView subclass:#InspectorListView
-	instanceVariableNames:'actionHolder listHolder includesSelf'
+	instanceVariableNames:'actionHolder inspectorList includesSelf'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Inspector'
@@ -11,7 +11,8 @@
 
 examples
 "
-
+        open a list view on an instance
+                                                                        [exBegin]
         |top slv a|
 
         a := OrderedCollection new.
@@ -27,129 +28,54 @@
         slv inspect:top.
         slv action:[:el|Transcript showCR:(el printString)].
         top open
+                                                                        [exEnd]
 "
 ! !
 
-!InspectorListView methodsFor:'accessing actions'!
-
-action:aOneArgAction
-    "set the single click action block.
-     If non-nil, that one is evaluated on single click, passing the
-     selected instance as argument
-    "
-    actionHolder := aOneArgAction
-! !
-
-!InspectorListView methodsFor:'accessing attributes'!
-
-includesSelf
-    ^ includesSelf
-!
+!InspectorListView methodsFor:'accessing'!
 
 includesSelf:aBool
     includesSelf := aBool
 !
 
-inspectedObject
-    ^ listHolder inspectedObject
-!
-
-isEmpty
-    "returns true if view is empty
-    "
-    ^ listHolder size == 0
-!
-
-listHolder
-    ^ listHolder
+list
+    ^ inspectorList
 !
 
-notEmpty
-    "returns true if view is empty
+list:aList
+    "set the lists contents from another list
     "
-    ^ listHolder size ~~ 0
-! !
-
-!InspectorListView methodsFor:'accessing contents'!
+    |list selNr|
 
-updateFromList:aListHolder
-    "set the lists contents from a list
-    "
-    listHolder := aListHolder.
-    listHolder includesSelf:includesSelf.
+    aList notNil ifTrue:[inspectorList := aList list]
+                ifFalse:[inspectorList := InspectorList new].
 
-    super list:(listHolder instanceNames).
-    self setSelection:(listHolder selection).
-
+    inspectorList includesSelf:includesSelf.
+    super list:(inspectorList instanceNames).
 !
 
-updateFromView:aInspectorListView
-    "update contents from other view
+update
+    "update the current list
     "
-    self updateFromList:(aInspectorListView listHolder)
-!
+    inspectorList update.
+    super list:(inspectorList instanceNames).
 
-updateList 
-    "set the lists contents dependant on the object
-    "
-    self updateList:(listHolder inspectedObject) selection:selection.
 ! !
 
-!InspectorListView methodsFor:'actions'!
-
-accept:aText notifying:aView
-    "on error #Error is returned otherwise the inspected object instance
-    "
-    |res|
-
-    res := listHolder accept:aText notifying:aView.
-
-    res ~~ #Error ifTrue:[
-        super list:(listHolder instanceNames).
-        self setSelection:(listHolder selection)
-    ].
-    ^ res
-!
-
-doIt:aCode notifying:aView
-    "on success the value returned from parser is returned otherwise #Error
-    "
-    |res|
-
-    res := listHolder doIt:aCode notifying:aView.
+!InspectorListView methodsFor:'accessing actions'!
 
-    res ~~ #Error ifTrue:[
-        super list:(listHolder instanceNames).
-        self setSelection:(listHolder selection)
-    ].
-    ^ res
-
-!
-
-inspect:anObject
-    "inspect an object
+action:aOneArgAction
+    "set the single click action block. If non-nil, that one is evaluated on single
+     click, passing the selected instance as argument
     "
-    ^ self inspect:anObject selection:nil
-!
-
-inspect:anObject selection:aNumber
-    "inspect an object and set the selection
-    "
-    aNumber notNil ifTrue:[
-        selection := aNumber
-    ] ifFalse:[
-        (listHolder inspectedObject) ~~ anObject ifTrue:[
-            selection := nil
-        ]
-    ].
-    self updateList:anObject selection:selection
+    actionHolder := aOneArgAction
 ! !
 
 !InspectorListView methodsFor:'drawing'!
 
 drawVisibleLineSelected:visLineNr with:fg and:bg
-    "redraw a single line as selected."
-
+    "redraw a single line as selected.
+    "
     |nr| 
 
     (nr := self visibleLineToListLine:visLineNr) notNil ifTrue:[
@@ -160,13 +86,13 @@
 !
 
 redrawArrowVisibleLine:visLineNr
-    "draw a right arrow for visible line"
-
+    "draw a right arrow for visible line
+    "
     |nr|
 
     nr := self visibleLineToListLine:visLineNr.
 
-    (listHolder instanceTypeAt:nr) == #directory ifTrue:[
+    (inspectorList instanceTypeAt:nr) == #directory ifTrue:[
         self drawRightArrowInVisibleLine:visLineNr
     ]
 
@@ -191,9 +117,11 @@
 !
 
 visibleLineNeedsSpecialCare:visLineNr
+    "returns true if the visible line needs special care
+    "
     |nr|
 
-    (listHolder instanceTypeAt:nr) == #directory ifTrue:[
+    (inspectorList instanceTypeAt:nr) == #directory ifTrue:[
         ^ true
     ].
     ^ super visibleLineNeedsSpecialCare:visLineNr
@@ -212,8 +140,8 @@
 !InspectorListView methodsFor:'event handling'!
 
 sizeChanged:how
-    "redraw marks"
-
+    "redraw marks
+    "
     super sizeChanged:how.
     shown ifTrue:[self invalidate]
 
@@ -229,7 +157,7 @@
     ignoreReselect := false.
     includesSelf   := false.
     actionHolder   := [:el|].
-    listHolder     := InspectorList for:nil.
+    inspectorList  := InspectorList new.
 
     actionBlock := [:dummy|
         self setSelection:selection.
@@ -239,60 +167,99 @@
 
 !InspectorListView methodsFor:'private'!
 
-updateList:inspObject selection:aSelection
-    "set the lists contents dependant on the object
+doesNotUnderstand:aMessage
+    "forward a message to the inspectorList
     "
-    listHolder := InspectorList for:inspObject.
-    listHolder includesSelf:includesSelf.
-    super list:(listHolder instanceNames).
+    (inspectorList respondsTo:(aMessage selector)) ifTrue:[
+        ^ aMessage sendTo:inspectorList
+    ].
+    ^ super doesNotUnderstand:aMessage
+
+
+!
+
+list:aCollection keepSelection:aBoolean
+    "set the list - redefined, since setting the list implies unselecting
+     and clearing attributes."
+
+    |oldSelection|
 
-    aSelection notNil ifTrue:[
-        self setSelection:aSelection
-    ] ifFalse:[
-        includesSelf ifTrue:[
-            self setSelection:1
-        ]
-    ]
+    "somewhat of a kludge: if selection is first line,
+     we have to remove the highlight frame by hand here"
+
+    (shown and:[hilightLevel ~~ 0]) ifTrue:[
+        selection == firstLineShown ifTrue:[
+           self paint:bgColor.
+           self fillRectangleX:margin y:margin
+                          width:(width - (margin * 2)) 
+                         height:(hilightLevel abs).
+        ].
+    ].
+    listAttributes := nil.
+    super list:aCollection expandTabs:false.
+    super setSelection:(inspectorList selection).
+
+
+
+
 ! !
 
 !InspectorListView methodsFor:'selections'!
 
-selectedInstanceName
-    "returns the name assigned to the selected instance or nil
+setSelection:aNumberOrNil
+    "select line, aNumber or deselect if argument is nil
+    "
+    |oldSize|
+
+    oldSize := inspectorList size.
+    inspectorList setSelection:aNumberOrNil.
+    oldSize == inspectorList size ifTrue:[super setSelection:(inspectorList selection)]
+                                 ifFalse:[super list:(inspectorList instanceNames)].
+! !
+
+!InspectorListView 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.
     "
-    ^ listHolder instanceNameAt:selection
+    |res|
+
+    res := inspectorList accept:aText notifying:aView.
+
+    res ~~ #Error ifTrue:[
+        super list:(inspectorList instanceNames)
+    ].
+    ^ res
+!
+
+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.
+    "
+    |res|
+
+    res := inspectorList doIt:aCode notifying:aView.
+
+    res ~~ #Error ifTrue:[
+        super list:(inspectorList instanceNames)
+    ].
+    ^ res
 
 !
 
-selectedInstanceType
-    "returns the type of the selected instance or nil
-     known types are: #directory #normal or:#self
+inspect:anObject
+    "inspect a new instance; update contents
     "
-    ^ listHolder instanceTypeAt:selection
-!
-
-selectedInstanceVar
-    "returns the value assigned to the selected instance or nil
-    "
-    ^ listHolder instanceVarAt:selection
-
-!
+    (inspectorList inspectedObject) == anObject ifTrue:[
+        ^ self update
+    ].
+    inspectorList := InspectorList for:anObject.
+    inspectorList includesSelf:includesSelf.
 
-setSelection:aNumberOrNil
-    "select line, aNumber or deselect if argument is nil
-    "
-    |type|
-
-    aNumberOrNil notNil ifTrue:[
-        type := listHolder instanceTypeAt:aNumberOrNil.
-        listHolder selection:aNumberOrNil.
-
-        type == #grow ifTrue:[
-            super list:(listHolder instanceNames)
-        ]
-    ].
-    super setSelection:aNumberOrNil
-
+    super list:(inspectorList instanceNames).
 ! !
 
 !InspectorListView class methodsFor:'documentation'!
--- a/InspectorPanelView.st	Wed Jan 15 14:32:46 1997 +0100
+++ b/InspectorPanelView.st	Wed Jan 15 14:33:11 1997 +0100
@@ -15,6 +15,7 @@
     example 1
     =========
 
+                                                                        [exBegin]
     |top slv|
 
     top := StandardSystemView new extent:600@400.
@@ -22,11 +23,12 @@
     slv inspect:top.
     slv action:[:el|Transcript showCR:el].
     top open.
+                                                                        [exEnd]
 
 
     example 2
     =========
-
+                                                                        [exBegin]
     |top slv edt a vvp|
 
     a := Array new:5.
@@ -44,16 +46,14 @@
     slv inspect:a.
 
     top open.
-
-
-
+                                                                        [exEnd]
 "
 ! !
 
 !InspectorPanelView class methodsFor:'constants'!
 
 minDepth
-    "returns the maximum of views
+    "returns the minimum of views assigned to a panel
     "
     ^ 4
 ! !
@@ -138,43 +138,33 @@
 inspectedObject
     "returns the current inspected object
     "
-    |i el|
-
-    rightHistory notEmpty ifTrue:[
-        el := rightHistory last
-    ] ifFalse:[
-        el := listViews findLast:[:v|v hasSelection].
-        el := listViews at:el.
-    ].
-    ^ el inspectedObject
+    ^ self findLastValidListWithSelection inspectedObject
 !
 
 selectedInstanceVar
     "returns the current selected instance var
     "
-    |el|
-
-    rightHistory notEmpty ifTrue:[
-        el := rightHistory last
-    ] ifFalse:[
-        el := listViews findLast:[:v|v hasSelection].
-        el := listViews at:el
-    ].
-    ^ el selectedInstanceVar
+    ^ self findLastValidListWithSelection selectedInstanceVar
 ! !
 
 !InspectorPanelView methodsFor:'actions'!
 
 accept:aText notifying:aView
-    self doItOrAccept:[:v|v accept:aText notifying:aView]
+    "evaluating aText on the last selected instance var. on success the views
+     are updated.
+    "
+    self doItOrAccept:[:aList|aList accept:aText notifying:aView]
 !
 
 doIt:aCode notifying:aView
-    ^ self doItOrAccept:[:v|v doIt:aCode notifying:aView]
+    "evaluating aCode on the selected instance var; on success the views
+     are updated.
+    "
+    ^ self doItOrAccept:[:aList|aList doIt:aCode notifying:aView]
 !
 
 inspect:anObject
-    "change the inspected object
+    "change the inspected object and all views
     "
     |view|
 
@@ -190,12 +180,15 @@
 !InspectorPanelView methodsFor:'event handling'!
 
 handlesKeyPress:key inView:someView
+    "all keys are handled by this instance itself
+    "
     ^ true
 
 !
 
 keyPress:key x:x y:y view:someView
-
+    "handle some special keys
+    "
     key == #CursorLeft  ifTrue:[^ self moveContentsRight:1].
     key == #CursorRight ifTrue:[^ self moveContentsLeft:1 ].
 
@@ -204,7 +197,7 @@
 !
 
 singleClickAt:anIndex
-    "the view changed its selection caused by a single click
+    "the view at an index changed its selection caused by a single click
     "
     |view start sivar|
 
@@ -486,12 +479,12 @@
     view hasSelection ifFalse:[^ nil].
     inst := view selectedInstanceVar.
 
-    menu := PopUpMenu labels:#( 'update' '-')
-                   selectors:#( #update  nil)
+    menu := PopUpMenu labels:#( 'update' )
+                   selectors:#( #update  )
                     receiver:self.
 
     menu actionAt:#update put:[
-        view updateList.
+        view update.
 
         listViews from:(anIndex + 1) do:[:v|
             (view selectedInstanceType) ~~ #directory ifTrue:[
@@ -504,12 +497,18 @@
         self update
     ].
 
+    (InspectorList isTraceable:inst) ifFalse:[
+        ^ menu
+    ].
+
     menu  addLabels:#(
+                      '-'
                       'trace'
                       'trap'
                       'untrace / untrap'
                      )
           selectors:#(
+                      nil
                       trace
                       trap
                       untrace
@@ -537,44 +536,48 @@
 !InspectorPanelView methodsFor:'private'!
 
 doItOrAccept:aBlock
-    "handle a doIt or accept action
+    "handle a doIt or accept action; on success all the folloed views are
+     updated
     "
-    |index view ivar rslt last stop|
+    |index list result instVar|
 
-    last := listViews last.
-    self moveContentsLeft:(rightHistory size).
+    list    := self findLastValidListWithSelection.
+    result  := aBlock value:list.
+    instVar := list selectedInstanceVar.
+    index   := listViews findLast:[:v|v == list].
 
-    last hasSelection ifTrue:[
-        self moveContentsLeft:1.
-        index := (listViews size) - 1
-    ] ifFalse:[
-        index := listViews findLast:[:v|v hasSelection].
+    (index ~~ 0 and:[index ~~ listViews size]) ifTrue:[
+        index := index + 1.
+        (list selectedInstanceType) == #directory ifTrue:[
+            (listViews at:index) inspect:instVar
+        ] ifFalse:[
+            (listViews at:index) inspect:nil
+        ].
+        self update
+    ].
+    valueChangedAction notNil ifTrue:[
+        valueChangedAction value:instVar
     ].
+    ^ result
+!
+
+findLastValidListWithSelection
+    "returns last valid list with a selection; if no selection exists in any
+     view, the list assigned to the inspected object is returned
+    "
+    |index|
+
+    rightHistory notEmpty ifTrue:[
+        ^ rightHistory first
+    ].
+    index := listViews findLast:[:v| v hasSelection ].
 
     index ~~ 0 ifTrue:[
-        view := listViews at:index.
-        rslt := aBlock value:view.
-        stop := listViews size.
-        ivar := view selectedInstanceVar.
-
-        index == stop ifTrue:[
-            self moveContentsLeft:1.
-        ] ifFalse:[
-            index := index + 1.
+        ^ listViews at:index
+    ].
 
-            (view selectedInstanceType) == #directory ifTrue:[
-                (listViews at:index) inspect:ivar
-            ] ifFalse:[
-                (listViews at:index) inspect:nil
-            ].
-            self update.
-        ].
-
-        valueChangedAction notNil ifTrue:[
-            valueChangedAction value:ivar
-        ]
-    ].
-    ^ rslt
+    leftHistory notEmpty ifTrue:[^ leftHistory last]
+                        ifFalse:[^ listViews at:1]
 !
 
 update
@@ -648,7 +651,7 @@
 !
 
 createViewWithoutRedraw
-    "add a new view at end
+    "add a new view at end of the panel
     "
     |view frame label index|
 
@@ -688,7 +691,7 @@
 !InspectorPanelView methodsFor:'scrolling-basic'!
 
 moveContentsLeft:nTimes
-    "move the contents of each view one position left
+    "move the contents of all views one position left
     "
     |fView stop assoc inspObj pView index|
 
@@ -702,14 +705,14 @@
     pView := listViews at:stop.
 
 
-    [   leftHistory add:fView listHolder.
+    [   leftHistory add:(fView list).
 
         1 to:stop do:[:i|
-            (listViews at:i) updateFromView:(listViews at:(i+1))
+            (listViews at:i) list:(listViews at:(i+1))
         ].
 
         rightHistory notEmpty ifTrue:[
-            (listViews last) updateFromList:(rightHistory removeLast)
+            (listViews last) list:(rightHistory removeLast)
         ] ifFalse:[
             (listViews last) inspect:(pView selectedInstanceVar)
         ].
@@ -724,7 +727,7 @@
 !
 
 moveContentsRight:nTimes
-    "move the contents of all listViews one position right
+    "move the contents of all views one position right
     "
     |view assoc size index lView fView|
 
@@ -740,12 +743,12 @@
 
         1 to:index do:[:i|
             lView hasSelection ifTrue:[
-                rightHistory add:(lView listHolder)
+                rightHistory add:(lView list)
             ].
             size to:2 by:-1 do:[:i|
-                (listViews at:i) updateFromView:(listViews at:(i-1))
+                (listViews at:i) list:(listViews at:(i-1))
             ].
-            fView updateFromList:(leftHistory removeLast)
+            fView list:(leftHistory removeLast)
         ].
         self update
     ]
@@ -753,7 +756,7 @@
 !
 
 scrollTo:nPercent
-    "set views dependant on scroll bar
+    "set views and contents dependant on scroll bar
     "
     |dY no noScr pR|
 
--- a/InspectorView.st	Wed Jan 15 14:32:46 1997 +0100
+++ b/InspectorView.st	Wed Jan 15 14:33:11 1997 +0100
@@ -12,7 +12,14 @@
 examples
 
 "
-NewInspector::InspectorView inspect:(Array new:5)
+    open an inspector on an array
+                                                                        [exBegin]
+    |array|
+
+    array := Array new:5.
+    array at:1 put:(Array new:400).
+    NewInspector::InspectorView inspect:array
+                                                                        [exEnd]
 "
 ! !
 
--- a/NewInspectorListView.st	Wed Jan 15 14:32:46 1997 +0100
+++ b/NewInspectorListView.st	Wed Jan 15 14:33:11 1997 +0100
@@ -1,7 +1,7 @@
 "{ NameSpace: NewInspector }"
 
 SelectionInListView subclass:#InspectorListView
-	instanceVariableNames:'actionHolder listHolder includesSelf'
+	instanceVariableNames:'actionHolder inspectorList includesSelf'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Inspector'
@@ -11,7 +11,8 @@
 
 examples
 "
-
+        open a list view on an instance
+                                                                        [exBegin]
         |top slv a|
 
         a := OrderedCollection new.
@@ -27,129 +28,54 @@
         slv inspect:top.
         slv action:[:el|Transcript showCR:(el printString)].
         top open
+                                                                        [exEnd]
 "
 ! !
 
-!InspectorListView methodsFor:'accessing actions'!
-
-action:aOneArgAction
-    "set the single click action block.
-     If non-nil, that one is evaluated on single click, passing the
-     selected instance as argument
-    "
-    actionHolder := aOneArgAction
-! !
-
-!InspectorListView methodsFor:'accessing attributes'!
-
-includesSelf
-    ^ includesSelf
-!
+!InspectorListView methodsFor:'accessing'!
 
 includesSelf:aBool
     includesSelf := aBool
 !
 
-inspectedObject
-    ^ listHolder inspectedObject
-!
-
-isEmpty
-    "returns true if view is empty
-    "
-    ^ listHolder size == 0
-!
-
-listHolder
-    ^ listHolder
+list
+    ^ inspectorList
 !
 
-notEmpty
-    "returns true if view is empty
+list:aList
+    "set the lists contents from another list
     "
-    ^ listHolder size ~~ 0
-! !
-
-!InspectorListView methodsFor:'accessing contents'!
+    |list selNr|
 
-updateFromList:aListHolder
-    "set the lists contents from a list
-    "
-    listHolder := aListHolder.
-    listHolder includesSelf:includesSelf.
+    aList notNil ifTrue:[inspectorList := aList list]
+                ifFalse:[inspectorList := InspectorList new].
 
-    super list:(listHolder instanceNames).
-    self setSelection:(listHolder selection).
-
+    inspectorList includesSelf:includesSelf.
+    super list:(inspectorList instanceNames).
 !
 
-updateFromView:aInspectorListView
-    "update contents from other view
+update
+    "update the current list
     "
-    self updateFromList:(aInspectorListView listHolder)
-!
+    inspectorList update.
+    super list:(inspectorList instanceNames).
 
-updateList 
-    "set the lists contents dependant on the object
-    "
-    self updateList:(listHolder inspectedObject) selection:selection.
 ! !
 
-!InspectorListView methodsFor:'actions'!
-
-accept:aText notifying:aView
-    "on error #Error is returned otherwise the inspected object instance
-    "
-    |res|
-
-    res := listHolder accept:aText notifying:aView.
-
-    res ~~ #Error ifTrue:[
-        super list:(listHolder instanceNames).
-        self setSelection:(listHolder selection)
-    ].
-    ^ res
-!
-
-doIt:aCode notifying:aView
-    "on success the value returned from parser is returned otherwise #Error
-    "
-    |res|
-
-    res := listHolder doIt:aCode notifying:aView.
+!InspectorListView methodsFor:'accessing actions'!
 
-    res ~~ #Error ifTrue:[
-        super list:(listHolder instanceNames).
-        self setSelection:(listHolder selection)
-    ].
-    ^ res
-
-!
-
-inspect:anObject
-    "inspect an object
+action:aOneArgAction
+    "set the single click action block. If non-nil, that one is evaluated on single
+     click, passing the selected instance as argument
     "
-    ^ self inspect:anObject selection:nil
-!
-
-inspect:anObject selection:aNumber
-    "inspect an object and set the selection
-    "
-    aNumber notNil ifTrue:[
-        selection := aNumber
-    ] ifFalse:[
-        (listHolder inspectedObject) ~~ anObject ifTrue:[
-            selection := nil
-        ]
-    ].
-    self updateList:anObject selection:selection
+    actionHolder := aOneArgAction
 ! !
 
 !InspectorListView methodsFor:'drawing'!
 
 drawVisibleLineSelected:visLineNr with:fg and:bg
-    "redraw a single line as selected."
-
+    "redraw a single line as selected.
+    "
     |nr| 
 
     (nr := self visibleLineToListLine:visLineNr) notNil ifTrue:[
@@ -160,13 +86,13 @@
 !
 
 redrawArrowVisibleLine:visLineNr
-    "draw a right arrow for visible line"
-
+    "draw a right arrow for visible line
+    "
     |nr|
 
     nr := self visibleLineToListLine:visLineNr.
 
-    (listHolder instanceTypeAt:nr) == #directory ifTrue:[
+    (inspectorList instanceTypeAt:nr) == #directory ifTrue:[
         self drawRightArrowInVisibleLine:visLineNr
     ]
 
@@ -191,9 +117,11 @@
 !
 
 visibleLineNeedsSpecialCare:visLineNr
+    "returns true if the visible line needs special care
+    "
     |nr|
 
-    (listHolder instanceTypeAt:nr) == #directory ifTrue:[
+    (inspectorList instanceTypeAt:nr) == #directory ifTrue:[
         ^ true
     ].
     ^ super visibleLineNeedsSpecialCare:visLineNr
@@ -212,8 +140,8 @@
 !InspectorListView methodsFor:'event handling'!
 
 sizeChanged:how
-    "redraw marks"
-
+    "redraw marks
+    "
     super sizeChanged:how.
     shown ifTrue:[self invalidate]
 
@@ -229,7 +157,7 @@
     ignoreReselect := false.
     includesSelf   := false.
     actionHolder   := [:el|].
-    listHolder     := InspectorList for:nil.
+    inspectorList  := InspectorList new.
 
     actionBlock := [:dummy|
         self setSelection:selection.
@@ -239,60 +167,99 @@
 
 !InspectorListView methodsFor:'private'!
 
-updateList:inspObject selection:aSelection
-    "set the lists contents dependant on the object
+doesNotUnderstand:aMessage
+    "forward a message to the inspectorList
     "
-    listHolder := InspectorList for:inspObject.
-    listHolder includesSelf:includesSelf.
-    super list:(listHolder instanceNames).
+    (inspectorList respondsTo:(aMessage selector)) ifTrue:[
+        ^ aMessage sendTo:inspectorList
+    ].
+    ^ super doesNotUnderstand:aMessage
+
+
+!
+
+list:aCollection keepSelection:aBoolean
+    "set the list - redefined, since setting the list implies unselecting
+     and clearing attributes."
+
+    |oldSelection|
 
-    aSelection notNil ifTrue:[
-        self setSelection:aSelection
-    ] ifFalse:[
-        includesSelf ifTrue:[
-            self setSelection:1
-        ]
-    ]
+    "somewhat of a kludge: if selection is first line,
+     we have to remove the highlight frame by hand here"
+
+    (shown and:[hilightLevel ~~ 0]) ifTrue:[
+        selection == firstLineShown ifTrue:[
+           self paint:bgColor.
+           self fillRectangleX:margin y:margin
+                          width:(width - (margin * 2)) 
+                         height:(hilightLevel abs).
+        ].
+    ].
+    listAttributes := nil.
+    super list:aCollection expandTabs:false.
+    super setSelection:(inspectorList selection).
+
+
+
+
 ! !
 
 !InspectorListView methodsFor:'selections'!
 
-selectedInstanceName
-    "returns the name assigned to the selected instance or nil
+setSelection:aNumberOrNil
+    "select line, aNumber or deselect if argument is nil
+    "
+    |oldSize|
+
+    oldSize := inspectorList size.
+    inspectorList setSelection:aNumberOrNil.
+    oldSize == inspectorList size ifTrue:[super setSelection:(inspectorList selection)]
+                                 ifFalse:[super list:(inspectorList instanceNames)].
+! !
+
+!InspectorListView 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.
     "
-    ^ listHolder instanceNameAt:selection
+    |res|
+
+    res := inspectorList accept:aText notifying:aView.
+
+    res ~~ #Error ifTrue:[
+        super list:(inspectorList instanceNames)
+    ].
+    ^ res
+!
+
+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.
+    "
+    |res|
+
+    res := inspectorList doIt:aCode notifying:aView.
+
+    res ~~ #Error ifTrue:[
+        super list:(inspectorList instanceNames)
+    ].
+    ^ res
 
 !
 
-selectedInstanceType
-    "returns the type of the selected instance or nil
-     known types are: #directory #normal or:#self
+inspect:anObject
+    "inspect a new instance; update contents
     "
-    ^ listHolder instanceTypeAt:selection
-!
-
-selectedInstanceVar
-    "returns the value assigned to the selected instance or nil
-    "
-    ^ listHolder instanceVarAt:selection
-
-!
+    (inspectorList inspectedObject) == anObject ifTrue:[
+        ^ self update
+    ].
+    inspectorList := InspectorList for:anObject.
+    inspectorList includesSelf:includesSelf.
 
-setSelection:aNumberOrNil
-    "select line, aNumber or deselect if argument is nil
-    "
-    |type|
-
-    aNumberOrNil notNil ifTrue:[
-        type := listHolder instanceTypeAt:aNumberOrNil.
-        listHolder selection:aNumberOrNil.
-
-        type == #grow ifTrue:[
-            super list:(listHolder instanceNames)
-        ]
-    ].
-    super setSelection:aNumberOrNil
-
+    super list:(inspectorList instanceNames).
 ! !
 
 !InspectorListView class methodsFor:'documentation'!
--- a/NewInspectorPanelView.st	Wed Jan 15 14:32:46 1997 +0100
+++ b/NewInspectorPanelView.st	Wed Jan 15 14:33:11 1997 +0100
@@ -15,6 +15,7 @@
     example 1
     =========
 
+                                                                        [exBegin]
     |top slv|
 
     top := StandardSystemView new extent:600@400.
@@ -22,11 +23,12 @@
     slv inspect:top.
     slv action:[:el|Transcript showCR:el].
     top open.
+                                                                        [exEnd]
 
 
     example 2
     =========
-
+                                                                        [exBegin]
     |top slv edt a vvp|
 
     a := Array new:5.
@@ -44,16 +46,14 @@
     slv inspect:a.
 
     top open.
-
-
-
+                                                                        [exEnd]
 "
 ! !
 
 !InspectorPanelView class methodsFor:'constants'!
 
 minDepth
-    "returns the maximum of views
+    "returns the minimum of views assigned to a panel
     "
     ^ 4
 ! !
@@ -138,43 +138,33 @@
 inspectedObject
     "returns the current inspected object
     "
-    |i el|
-
-    rightHistory notEmpty ifTrue:[
-        el := rightHistory last
-    ] ifFalse:[
-        el := listViews findLast:[:v|v hasSelection].
-        el := listViews at:el.
-    ].
-    ^ el inspectedObject
+    ^ self findLastValidListWithSelection inspectedObject
 !
 
 selectedInstanceVar
     "returns the current selected instance var
     "
-    |el|
-
-    rightHistory notEmpty ifTrue:[
-        el := rightHistory last
-    ] ifFalse:[
-        el := listViews findLast:[:v|v hasSelection].
-        el := listViews at:el
-    ].
-    ^ el selectedInstanceVar
+    ^ self findLastValidListWithSelection selectedInstanceVar
 ! !
 
 !InspectorPanelView methodsFor:'actions'!
 
 accept:aText notifying:aView
-    self doItOrAccept:[:v|v accept:aText notifying:aView]
+    "evaluating aText on the last selected instance var. on success the views
+     are updated.
+    "
+    self doItOrAccept:[:aList|aList accept:aText notifying:aView]
 !
 
 doIt:aCode notifying:aView
-    ^ self doItOrAccept:[:v|v doIt:aCode notifying:aView]
+    "evaluating aCode on the selected instance var; on success the views
+     are updated.
+    "
+    ^ self doItOrAccept:[:aList|aList doIt:aCode notifying:aView]
 !
 
 inspect:anObject
-    "change the inspected object
+    "change the inspected object and all views
     "
     |view|
 
@@ -190,12 +180,15 @@
 !InspectorPanelView methodsFor:'event handling'!
 
 handlesKeyPress:key inView:someView
+    "all keys are handled by this instance itself
+    "
     ^ true
 
 !
 
 keyPress:key x:x y:y view:someView
-
+    "handle some special keys
+    "
     key == #CursorLeft  ifTrue:[^ self moveContentsRight:1].
     key == #CursorRight ifTrue:[^ self moveContentsLeft:1 ].
 
@@ -204,7 +197,7 @@
 !
 
 singleClickAt:anIndex
-    "the view changed its selection caused by a single click
+    "the view at an index changed its selection caused by a single click
     "
     |view start sivar|
 
@@ -486,12 +479,12 @@
     view hasSelection ifFalse:[^ nil].
     inst := view selectedInstanceVar.
 
-    menu := PopUpMenu labels:#( 'update' '-')
-                   selectors:#( #update  nil)
+    menu := PopUpMenu labels:#( 'update' )
+                   selectors:#( #update  )
                     receiver:self.
 
     menu actionAt:#update put:[
-        view updateList.
+        view update.
 
         listViews from:(anIndex + 1) do:[:v|
             (view selectedInstanceType) ~~ #directory ifTrue:[
@@ -504,12 +497,18 @@
         self update
     ].
 
+    (InspectorList isTraceable:inst) ifFalse:[
+        ^ menu
+    ].
+
     menu  addLabels:#(
+                      '-'
                       'trace'
                       'trap'
                       'untrace / untrap'
                      )
           selectors:#(
+                      nil
                       trace
                       trap
                       untrace
@@ -537,44 +536,48 @@
 !InspectorPanelView methodsFor:'private'!
 
 doItOrAccept:aBlock
-    "handle a doIt or accept action
+    "handle a doIt or accept action; on success all the folloed views are
+     updated
     "
-    |index view ivar rslt last stop|
+    |index list result instVar|
 
-    last := listViews last.
-    self moveContentsLeft:(rightHistory size).
+    list    := self findLastValidListWithSelection.
+    result  := aBlock value:list.
+    instVar := list selectedInstanceVar.
+    index   := listViews findLast:[:v|v == list].
 
-    last hasSelection ifTrue:[
-        self moveContentsLeft:1.
-        index := (listViews size) - 1
-    ] ifFalse:[
-        index := listViews findLast:[:v|v hasSelection].
+    (index ~~ 0 and:[index ~~ listViews size]) ifTrue:[
+        index := index + 1.
+        (list selectedInstanceType) == #directory ifTrue:[
+            (listViews at:index) inspect:instVar
+        ] ifFalse:[
+            (listViews at:index) inspect:nil
+        ].
+        self update
+    ].
+    valueChangedAction notNil ifTrue:[
+        valueChangedAction value:instVar
     ].
+    ^ result
+!
+
+findLastValidListWithSelection
+    "returns last valid list with a selection; if no selection exists in any
+     view, the list assigned to the inspected object is returned
+    "
+    |index|
+
+    rightHistory notEmpty ifTrue:[
+        ^ rightHistory first
+    ].
+    index := listViews findLast:[:v| v hasSelection ].
 
     index ~~ 0 ifTrue:[
-        view := listViews at:index.
-        rslt := aBlock value:view.
-        stop := listViews size.
-        ivar := view selectedInstanceVar.
-
-        index == stop ifTrue:[
-            self moveContentsLeft:1.
-        ] ifFalse:[
-            index := index + 1.
+        ^ listViews at:index
+    ].
 
-            (view selectedInstanceType) == #directory ifTrue:[
-                (listViews at:index) inspect:ivar
-            ] ifFalse:[
-                (listViews at:index) inspect:nil
-            ].
-            self update.
-        ].
-
-        valueChangedAction notNil ifTrue:[
-            valueChangedAction value:ivar
-        ]
-    ].
-    ^ rslt
+    leftHistory notEmpty ifTrue:[^ leftHistory last]
+                        ifFalse:[^ listViews at:1]
 !
 
 update
@@ -648,7 +651,7 @@
 !
 
 createViewWithoutRedraw
-    "add a new view at end
+    "add a new view at end of the panel
     "
     |view frame label index|
 
@@ -688,7 +691,7 @@
 !InspectorPanelView methodsFor:'scrolling-basic'!
 
 moveContentsLeft:nTimes
-    "move the contents of each view one position left
+    "move the contents of all views one position left
     "
     |fView stop assoc inspObj pView index|
 
@@ -702,14 +705,14 @@
     pView := listViews at:stop.
 
 
-    [   leftHistory add:fView listHolder.
+    [   leftHistory add:(fView list).
 
         1 to:stop do:[:i|
-            (listViews at:i) updateFromView:(listViews at:(i+1))
+            (listViews at:i) list:(listViews at:(i+1))
         ].
 
         rightHistory notEmpty ifTrue:[
-            (listViews last) updateFromList:(rightHistory removeLast)
+            (listViews last) list:(rightHistory removeLast)
         ] ifFalse:[
             (listViews last) inspect:(pView selectedInstanceVar)
         ].
@@ -724,7 +727,7 @@
 !
 
 moveContentsRight:nTimes
-    "move the contents of all listViews one position right
+    "move the contents of all views one position right
     "
     |view assoc size index lView fView|
 
@@ -740,12 +743,12 @@
 
         1 to:index do:[:i|
             lView hasSelection ifTrue:[
-                rightHistory add:(lView listHolder)
+                rightHistory add:(lView list)
             ].
             size to:2 by:-1 do:[:i|
-                (listViews at:i) updateFromView:(listViews at:(i-1))
+                (listViews at:i) list:(listViews at:(i-1))
             ].
-            fView updateFromList:(leftHistory removeLast)
+            fView list:(leftHistory removeLast)
         ].
         self update
     ]
@@ -753,7 +756,7 @@
 !
 
 scrollTo:nPercent
-    "set views dependant on scroll bar
+    "set views and contents dependant on scroll bar
     "
     |dY no noScr pR|
 
--- a/NewInspectorView.st	Wed Jan 15 14:32:46 1997 +0100
+++ b/NewInspectorView.st	Wed Jan 15 14:33:11 1997 +0100
@@ -12,7 +12,14 @@
 examples
 
 "
-NewInspector::InspectorView inspect:(Array new:5)
+    open an inspector on an array
+                                                                        [exBegin]
+    |array|
+
+    array := Array new:5.
+    array at:1 put:(Array new:400).
+    NewInspector::InspectorView inspect:array
+                                                                        [exEnd]
 "
 ! !