*** empty log message ***
authorClaus Gittinger <cg@exept.de>
Wed, 08 Sep 1999 19:40:37 +0200
changeset 1213 6cf7a4c2dfce
parent 1212 a13dafe6f9fe
child 1214 02a032b1098c
*** empty log message ***
InspectorList.st
InspectorListView.st
InspectorPanelView.st
InspectorView.st
Make.proto
NewInspectorList.st
NewInspectorListView.st
NewInspectorPanelView.st
NewInspectorView.st
--- a/InspectorList.st	Wed Sep 08 12:00:12 1999 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,495 +0,0 @@
-"
- COPYRIGHT (c) 1997 by eXept Software AG
-              All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
-
-
-"{ NameSpace: NewInspector }"
-
-Object subclass:#InspectorList
-	instanceVariableNames:'inspectedObject instanceNames instanceTypes selection'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Interface-Inspector'
-!
-
-!InspectorList class methodsFor:'documentation'!
-
-copyright
-"
- COPYRIGHT (c) 1997 by eXept Software AG
-              All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
-
-! !
-
-!InspectorList class methodsFor:'instance creation'!
-
-for:anObject
-    "create a new list for an instance
-    "
-    ^ 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
-
-
-! !
-
-!InspectorList class methodsFor:'testing'!
-
-isDirectory:anInstance
-    "returns true if the instance is a directory
-    "
-    |cls|
-
-    anInstance notNil ifTrue:[
-        cls := anInstance class.
-
-        cls == Character  ifTrue:[ ^ false ].
-        cls == Symbol     ifTrue:[ ^ false ].
-        cls == String     ifTrue:[ ^ false ].
-        cls == Float      ifTrue:[ ^ false ].
-        cls == ShortFloat ifTrue:[ ^ false ].
-
-        cls allInstVarNames notEmpty ifTrue:[
-            ^ true
-        ].
-
-        anInstance isVariable ifTrue:[
-            ^ true
-        ].
-    ].
-    ^ false
-
-    "Modified: / 4.2.1999 / 20:00:11 / cg"
-!
-
-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:aBoolean
-    "includes 'self' dependant on the boolean
-    "
-    (self includesSelf) ~~ aBoolean ifTrue:[
-        aBoolean ifTrue:[
-            instanceNames addFirst:'self'.
-            instanceTypes addFirst:#self.
-
-            selection notNil ifTrue:[selection := selection + 1]
-                            ifFalse:[selection := 1]
-
-        ] ifFalse:[
-            instanceNames removeFirst.
-            instanceTypes removeFirst.
-
-            selection isNil ifFalse:[
-                (selection := selection - 1) == 0 ifTrue:[
-                    selection := nil
-                ]
-            ]
-        ]
-    ]
-
-
-!
-
-list
-    "returns self
-    "
-    ^ self
-!
-
-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.
-    ]
-
-    "Modified: / 4.2.1999 / 20:00:38 / cg"
-! !
-
-!InspectorList methodsFor:'accessing contents'!
-
-inspectedObject
-    "returns current inspected object
-    "
-    ^ inspectedObject
-
-
-!
-
-instanceNames
-    "returns list of instance names
-    "
-    ^ instanceNames
-
-
-!
-
-instanceTypeAt:anIndex
-    "returns type assigned to the list entry (#directory #normal #self #grow)
-     In case of an invalid index nil is returned.
-    "
-    (anIndex isNil or:[anIndex > instanceTypes size]) ifFalse:[^ instanceTypes at:anIndex]
-                                                       ifTrue:[^ nil].
-
-
-!
-
-instanceTypes
-    "returns list of types (#directory #normal #self #grow)
-    "
-    ^ instanceTypes
-
-
-!
-
-instanceVarAt:anIndex
-    "returns the instnace variable assigned to the index or 
-     nil in case of an invalid index.
-    "
-    |nm|
-
-    (anIndex isNil or:[anIndex > instanceTypes size]) ifFalse:[
-        nm := instanceNames at:anIndex.
-
-        (nm at:1) isDigit ifFalse:[
-            self includesSelf ifFalse:[
-                ^ inspectedObject instVarAt:anIndex
-            ].
-            anIndex == 1 ifFalse:[^ inspectedObject instVarAt:(anIndex-1)]
-                          ifTrue:[^ inspectedObject]
-        ].
-      ^ inspectedObject basicAt:(Number readFrom:nm onError:0)
-    ].
-    ^ nil
-
-
-! !
-
-!InspectorList methodsFor:'initialization'!
-
-initialize
-    "initialize instance attributes
-    "
-    super initialize.
-
-    instanceNames := OrderedCollection new.
-    instanceTypes := OrderedCollection new.
-
-! !
-
-!InspectorList methodsFor:'private'!
-
-resizeTo:aNumber
-    "resize list to minimum aNumber
-    "
-    |lstVarId basicSize newLastId obj instSize|
-
-    (inspectedObject isVariable and:[self class isDirectory:inspectedObject]) ifFalse:[
-        ^ self
-    ].
-
-    instanceTypes size == 0 ifTrue:[
-        lstVarId := 0
-    ] ifFalse:[
-        instSize := inspectedObject class instSize.
-
-        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:[
-        lstVarId := lstVarId + 1.
-        obj := inspectedObject basicAt:lstVarId.
-
-        (self class isDirectory:obj) ifTrue:[instanceTypes add:#directory]
-                                    ifFalse:[instanceTypes add:#normal].
-
-        instanceNames add:(lstVarId printString, '   ', obj class name printString).
-    ].
-
-    lstVarId ~~ basicSize ifTrue:[
-        instanceNames add:'..'.
-        instanceTypes add:#grow
-    ].
-! !
-
-!InspectorList methodsFor:'selections'!
-
-selectedInstanceType
-    "returns type assigned to the selected list entry (#directory #normal #self #grow).
-     In case of no selection nil is returned.
-    "
-    ^ self instanceTypeAt:selection
-
-
-!
-
-selectedInstanceVar
-    "returns current inspected instance variable or nil
-    "
-    ^ self instanceVarAt:selection
-
-
-!
-
-selection
-    "returns current selection number or nil
-    "
-    ^ selection
-
-
-!
-
-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
-    "
-    ^ 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.
-
-            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.
-
-            evaluator notNil ifTrue:[
-                result := evaluator evaluate:code 
-                                          in:nil 
-                                    receiver:selInstVar 
-                                   notifying:aView 
-                                      logged:true 
-                                      ifFail:[successFg := false].
-
-                successFg ifTrue:[
-                    self update. 
-                  ^ result 
-                ]
-            ]
-        ]
-    ].
-    ^ #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'!
-
-version
-    ^ '$Header$'
-! !
--- a/InspectorListView.st	Wed Sep 08 12:00:12 1999 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,297 +0,0 @@
-"
- COPYRIGHT (c) 1997 by eXept Software AG
-              All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
-
-
-
-"{ NameSpace: NewInspector }"
-
-SelectionInListView subclass:#InspectorListView
-	instanceVariableNames:'actionHolder inspectorList includesSelf'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Interface-Inspector'
-!
-
-!InspectorListView class methodsFor:'documentation'!
-
-copyright
-"
- COPYRIGHT (c) 1997 by eXept Software AG
-              All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
-
-
-!
-
-examples
-"
-        open a list view on an instance
-                                                                        [exBegin]
-        |top slv a|
-
-        a := OrderedCollection new.
-        a add:1.
-
-        top := StandardSystemView new
-                label:'select';
-                extent:200@200.
-
-        slv := ScrollableView for:self in:top.
-        slv origin:0.0@0.0 corner:1.0@1.0.
-        slv := slv scrolledView.
-        slv inspect:top.
-        slv action:[:el|Transcript showCR:(el printString)].
-        top open
-                                                                        [exEnd]
-"
-! !
-
-!InspectorListView methodsFor:'accessing'!
-
-includesSelf:aBool
-    includesSelf := aBool
-!
-
-list
-    ^ inspectorList
-!
-
-list:aList
-    "set the lists contents from another list
-    "
-    aList notNil ifTrue:[inspectorList := aList list]
-                ifFalse:[inspectorList := InspectorList new].
-
-    inspectorList includesSelf:includesSelf.
-    super list:(inspectorList instanceNames).
-!
-
-update
-    "update the current list
-    "
-    inspectorList update.
-    super list:(inspectorList instanceNames).
-
-! !
-
-!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:'drawing'!
-
-drawVisibleLineSelected:visLineNr with:fg and:bg
-    "redraw a single line as selected.
-    "
-    |nr| 
-
-    (nr := self visibleLineToListLine:visLineNr) notNil ifTrue:[
-        ^ self drawVisibleLine:visLineNr with:fg and:bg.
-    ].
-    ^ super drawVisibleLine:visLineNr with:fg and:bg
-
-!
-
-redrawArrowVisibleLine:visLineNr
-    "draw a right arrow for visible line
-    "
-    |nr|
-
-    nr := self visibleLineToListLine:visLineNr.
-
-    (inspectorList instanceTypeAt:nr) == #directory ifTrue:[
-        self drawRightArrowInVisibleLine:visLineNr
-    ]
-
-
-!
-
-redrawFromVisibleLine:startVisLineNr to:endVisLineNr
-    "redefined to look for directory in every line
-    "
-    super redrawFromVisibleLine:startVisLineNr to:endVisLineNr.
-
-    startVisLineNr to:endVisLineNr do:[:visLineNr|
-        self redrawArrowVisibleLine:visLineNr
-    ]
-!
-
-redrawVisibleLine:visLineNr
-    "if the line is one for a directory, draw a right arrow
-    "
-    super redrawVisibleLine:visLineNr.
-    self  redrawArrowVisibleLine:visLineNr.
-!
-
-visibleLineNeedsSpecialCare:visLineNr
-    "returns true if the visible line needs special care
-    "
-    |nr|
-
-    nr := self visibleLineToListLine:visLineNr.
-
-    (inspectorList instanceTypeAt:nr) == #directory ifTrue:[
-        ^ true
-    ].
-    ^ super visibleLineNeedsSpecialCare:visLineNr
-
-!
-
-widthForScrollBetween:firstLine and:lastLine
-    "return the width in pixels for a scroll between firstLine and lastLine
-     - return full width here since there might be directory marks
-    "
-    ^ (width - margin - margin)
-
-
-! !
-
-!InspectorListView methodsFor:'event handling'!
-
-sizeChanged:how
-    "redraw marks
-    "
-    super sizeChanged:how.
-    shown ifTrue:[self invalidate]
-
-! !
-
-!InspectorListView methodsFor:'initialization'!
-
-initialize
-    "initialization
-    "
-    super initialize.
-
-    ignoreReselect := false.
-    includesSelf   := false.
-    actionHolder   := [:el|].
-    inspectorList  := InspectorList new.
-
-    actionBlock := [:dummy|
-        self setSelection:selection.
-        actionHolder value:(self selectedInstanceVar)
-    ].
-! !
-
-!InspectorListView methodsFor:'private'!
-
-doesNotUnderstand:aMessage
-    "forward a message to the inspectorList
-    "
-    (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."
-
-    "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'!
-
-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.
-    "
-    |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
-
-!
-
-inspect:anObject
-    "inspect a new instance; update contents
-    "
-    (inspectorList inspectedObject) == anObject ifTrue:[
-        ^ self update
-    ].
-    inspectorList := InspectorList for:anObject.
-    inspectorList includesSelf:includesSelf.
-
-    super list:(inspectorList instanceNames).
-! !
-
-!InspectorListView class methodsFor:'documentation'!
-
-version
-    ^ '$Header$'
-! !
--- a/InspectorPanelView.st	Wed Sep 08 12:00:12 1999 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,815 +0,0 @@
-"
- COPYRIGHT (c) 1997 by eXept Software AG
-              All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
-
-
-
-"{ NameSpace: NewInspector }"
-
-SimpleView subclass:#InspectorPanelView
-	instanceVariableNames:'frames labelViews listViews scrollBar maxDepth leftHistory
-		rightHistory hzpView actionBlock valueChangedAction'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Interface-Inspector'
-!
-
-!InspectorPanelView class methodsFor:'documentation'!
-
-copyright
-"
- COPYRIGHT (c) 1997 by eXept Software AG
-              All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
-
-
-!
-
-examples
-"
-    example 1
-    =========
-
-                                                                        [exBegin]
-    |top slv|
-
-    top := StandardSystemView new extent:600@400.
-    slv := NewInspector::InspectorPanelView origin:0.0@0.0 corner:1.0@1.0 in:top.
-    slv inspect:top.
-    slv action:[:el|Transcript showCR:el].
-    top open.
-                                                                        [exEnd]
-
-
-    example 2
-    =========
-                                                                        [exBegin]
-    |top slv edt a vvp|
-
-    a := Array new:5.
-    a at:4 put:(Array new:6).
-
-    top := StandardSystemView new extent:600@400.
-    vvp := VariableVerticalPanel origin:0.0@0.0  corner:1.0@1.0 in:top.
-
-    slv := NewInspector::InspectorPanelView origin:0.0@0.0 corner:1.0@0.5 in:vvp.
-    edt := Workspace origin:0.0 @ 0.5 corner:1.0 @ 1.0 in:vvp.
-    edt acceptAction:[:theText|slv accept:theText notifying:edt].
-    edt   doItAction:[:theCode|slv doIt:theCode   notifying:edt].
-
-    slv action:[:el| Transcript showCR:(el printString)].
-    slv inspect:a.
-
-    top open.
-                                                                        [exEnd]
-"
-! !
-
-!InspectorPanelView class methodsFor:'constants'!
-
-minDepth
-    "returns the minimum of views assigned to a panel
-    "
-    ^ 4
-! !
-
-!InspectorPanelView methodsFor:'accessing'!
-
-depth
-    "returns number of listViews
-    "
-  ^ listViews size
-!
-
-depth:aDepth
-    "change the number of existing listViews
-    "
-    |sz min|
-
-    min := self class minDepth.
-
-    aDepth > min ifTrue:[
-        sz := aDepth min:maxDepth.
-
-        sz < listViews size ifTrue:[
-            sz := listViews size
-        ]
-    ] ifFalse:[
-        sz := min
-    ].
-
-    listViews size == sz ifTrue:[
-        sz == aDepth ifFalse:[self moveContentsLeft:1].
-    ] ifFalse:[
-        [self createViewWithoutRedraw. listViews size ~~ sz] whileTrue.
-        self computeExtentOfFrames.
-
-        (self topView shown) ifTrue:[
-            hzpView sizeChanged:nil.
-            hzpView realizeAllSubViews.
-        ]
-    ]
-!
-
-maxDepth
-    ^ maxDepth
-!
-
-maxDepth:aNumber
-    "change max depth for instance
-    "
-    aNumber > listViews size ifTrue:[
-        aNumber >= (self class minDepth) ifTrue:[
-            maxDepth := aNumber.
-
-            maxDepth < listViews size ifTrue:[
-                self depth:maxDepth
-            ]
-        ]
-    ]
-! !
-
-!InspectorPanelView methodsFor:'accessing actions'!
-
-action:aOneArgBlock
-    "set the single click action block.
-     If non-nil, that one is evaluated on single click, passing the
-     selected instance as argument
-    "
-    actionBlock := aOneArgBlock
-
-
-!
-
-valueChangedAction:aOneArgBlock
-    "evaluated if an instnace changed its value; passing
-     the instance as argument
-    "
-    valueChangedAction := aOneArgBlock
-! !
-
-!InspectorPanelView methodsFor:'accessing selections'!
-
-inspectedObject
-    "returns the current inspected object
-    "
-    ^ self findLastValidListWithSelection inspectedObject
-!
-
-selectedInstanceVar
-    "returns the current selected instance var
-    "
-    ^ self findLastValidListWithSelection selectedInstanceVar
-! !
-
-!InspectorPanelView methodsFor:'actions'!
-
-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
-    "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 and all views
-    "
-    |view|
-
-    view := listViews first.
-    leftHistory  removeAll.
-    rightHistory removeAll.
-
-    view inspect:anObject.
-    listViews from:2 do:[:v|v inspect:nil].
-    self update.
-! !
-
-!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 ].
-
-    someView keyPress:key x:x y:y.
-
-!
-
-singleClickAt:anIndex
-    "the view at an index changed its selection caused by a single click
-    "
-    |view start sivar|
-
-    rightHistory removeAll.
-
-    view  := listViews at:anIndex.
-    start := anIndex + 1.
-    sivar := view selectedInstanceVar.
-
-    start > listViews size ifTrue:[
-        start >= maxDepth ifTrue:[
-            self moveContentsLeft:1.
-          ^ actionBlock value:sivar.
-        ].
-    ].
-
-    (view selectedInstanceType) == #directory ifTrue:[
-        (listViews at:start) setSelection:nil.
-        (listViews at:start) inspect:sivar.
-        
-        start := start + 1.
-    ].
-
-    listViews from:start do:[:v|v inspect:nil].
-    self update.
-    actionBlock value:sivar.
-! !
-
-!InspectorPanelView methodsFor:'initializing'!
-
-initialize
-    "initialize instance
-    "
-    super initialize.
-
-    frames       := OrderedCollection new.
-    listViews    := OrderedCollection new.
-    labelViews   := OrderedCollection new.
-    leftHistory  := OrderedCollection new.
-    rightHistory := OrderedCollection new.
-    maxDepth     := self class minDepth.
-
-    actionBlock := [:el| ].
-
-    hzpView    := VariableHorizontalPanel origin:0.0@0.0 corner:1.0@1.0 in:self.
-    scrollBar  := HorizontalScrollBar origin:0.0@1.0 corner:1.0@1.0 in:self.
-    scrollBar asynchronousOperation.
-
-    hzpView bottomInset:(scrollBar preferredExtent y).
-
-    scrollBar topInset:(scrollBar preferredExtent y) negated.
-    scrollBar thumbHeight:100.
-    scrollBar scrollAction:[:percent | self scrollTo:percent].
-    scrollBar scrollRightAction:[self moveContentsLeft:1].
-    scrollBar scrollLeftAction:[self moveContentsRight:1].
-
-    self depth:maxDepth.
-! !
-
-!InspectorPanelView methodsFor:'menu - labels & actions'!
-
-browse:anIndex
-    self classAtLabel:anIndex do:[:cls| cls browserClass openInClass:cls selector:nil ]
-
-!
-
-browseClassHierarchy:anIndex
-    self classAtLabel:anIndex do:[:cls| cls browserClass browseClassHierarchy:cls ]
-
-!
-
-browseFullClassProtocol:anIndex
-    self classAtLabel:anIndex do:[:cls| cls browserClass browseFullClassProtocol:cls ]
-
-!
-
-classAtLabel:anIndex do:anAction
-    "evaluate action on class assigned to label
-    "
-    |cls|
-
-    anIndex <= labelViews size ifTrue:[
-        (cls := Smalltalk classNamed:((labelViews at:anIndex) label)) notNil ifTrue:[
-            anAction value:cls
-        ]
-    ]
-
-!
-
-labelMenu
-    "popup menu required by any label. Delegate the request to the corresponding label
-    "
-    |sqNr view|
-
-    view := (WindowGroup lastEventQuerySignal raise) view.
-    sqNr := labelViews findFirst:[:v| v == view].
-
-    sqNr ~~ 0 ifTrue:[
-        view := labelViews at:sqNr.
-
-        view label notEmpty ifTrue:[
-            ^ self labelMenu:sqNr
-        ]
-    ].
-    ^ nil
-!
-
-labelMenu:anIndex
-    "popup menu required for a label identified by its sequence number
-    "
-    |menu|
-
-    menu := PopUpMenu labels:#(
-                              'browse'
-                              'browse class hierarchy'
-                              'browse full class protocol'
-                              )
-                   selectors:#( 
-                              browse:
-                              browseClassHierarchy:
-                              browseFullClassProtocol:
-                              )
-                    receiver:self.
-
-   menu args:(Array new:(menu labels size) withAll:anIndex).
- ^ menu
-
-! !
-
-!InspectorPanelView methodsFor:'menu - views & actions'!
-
-doTrace:anInstance
-    "place a trace on messages sent to the instance
-    "
-    |selectors|
-
-    selectors := self messageMenu:anInstance.
-
-    selectors notNil ifTrue:[
-        self topView withWaitCursorDo:[MessageTracer trace:anInstance selectors:selectors]
-    ].
-
-!
-
-doTraceAll:anInstance
-    "place a trace on all messages sent to the instance
-    "
-    self topView withWaitCursorDo:[MessageTracer traceAll:anInstance]
-!
-
-doTrap:anInstance
-    "place a trap on a message sent to the instance
-    "
-    |selectors|
-
-    selectors := self messageMenu:anInstance.
-
-    selectors notNil ifTrue:[
-        self topView withWaitCursorDo:[MessageTracer trap:anInstance selectors:selectors]
-    ]
-!
-
-doTrapAll:anInstance
-    "place a trap on all messages sent to the instance
-    "
-    self topView withWaitCursorDo:[MessageTracer trapAll:anInstance]
-
-!
-
-doUntrace:anInstance
-    "remove all traps and traces to the instance
-    "
-    self topView withWaitCursorDo:[MessageTracer untrace:anInstance].
-
-!
-
-messageMenu:anInstance
-    "open menu to select messages; on accepted a list of messages is returned
-    "
-    |sll acl lst inset top hzp slv acv dblClcAct btp b1 b2 accepted viewSpacing|
-
-    top := StandardSystemView new.
-    top extent:500 @ 400.
-    top label:(anInstance printString).
-
-    (Label origin:(0.0 @  0.0) corner:(0.5 @ 20) in:top) label:'messages'.
-    (Label origin:(0.5 @  0.0) corner:(1.0 @ 20) in:top) label:'selected'.
-    hzp := VariableHorizontalPanel origin:(0.0 @ 20) corner:(1.0 @ 1.0) in:top.
-    btp := HorizontalPanelView origin:(0.0 @1.0) corner:(1.0 @ 1.0) in:top.
-
-    b1 := Button abortButtonIn:btp.
-    b2 := Button okButtonIn:btp.
-    accepted := false.
-
-    b1 action:[accepted := false. top destroy].
-    b2 action:[accepted := true.  top destroy].
-
-    btp horizontalLayout:#fitSpace.
-    viewSpacing := top class viewSpacing.
-    inset       := (b2 preferredExtent y) + viewSpacing.
-    viewSpacing := viewSpacing // 2.
-
-    hzp bottomInset:inset.
-    btp topInset:((inset - viewSpacing) negated).
-    btp bottomInset:viewSpacing.
-
-    slv := ScrollableView for:SelectionInListView
-                miniScrollerV:true
-                       origin:(0.0 @ 0.0)
-                       corner:(0.5 @ 1.0)
-                           in:hzp.
-
-    acv := ScrollableView for:SelectionInListView
-                miniScrollerV:true
-                       origin:(0.5 @ 0.0)
-                       corner:(1.0 @ 1.0)
-                           in:hzp.
-
-    slv := slv scrolledView.
-    acv := acv scrolledView.
-
-    sll := (MessageTracer realClassOf:anInstance) selectors.
-    acl := OrderedCollection new.
-
-    (MessageTracer wrappedSelectorsOf:anInstance) do:[:el|
-        el notNil ifTrue:[
-            acl add:el.
-            sll remove:el ifAbsent:nil
-        ]
-    ].
-        
-    slv list:(sll copy).
-    acv list:(acl copy).
-
-    dblClcAct := [:from :to|
-        to add:(from selectionValue).
-        from removeIndex:(from selection).
-        from redraw.
-    ].
-
-    slv doubleClickAction:[:index| dblClcAct value:slv value:acv].
-    acv doubleClickAction:[:index| dblClcAct value:acv value:slv].
-
-    top openModal.
-
-    accepted ifFalse:[
-        ^ nil
-    ].
-    lst := acv list.
-
-"undo existing traps            HACK: removes traps and traces"
-
-    acl notEmpty ifTrue:[
-        MessageTracer untrace:anInstance
-    ].
-
-    lst notEmpty ifTrue:[^ lst]
-                ifFalse:[^ nil]
-!
-
-viewMenu
-    "popup menu required by any view. Delegate the request to the corresponding view
-    "
-    |sqNr view|
-
-    view := (WindowGroup lastEventQuerySignal raise) view.
-    sqNr := listViews findFirst:[:v| v == view].
-
-    sqNr notNil ifTrue:[^ self viewMenu:sqNr]
-               ifFalse:[^ nil]
-!
-
-viewMenu:anIndex
-    "popup menu required for a view identified by its sequence number
-    "
-    |view menu inst args lbls|
-
-    view := listViews at:anIndex.
-    view hasSelection ifFalse:[^ nil].
-    inst := view selectedInstanceVar.
-
-    menu := PopUpMenu labels:#( 'update' )
-                   selectors:#( #update  )
-                    receiver:self.
-
-    menu actionAt:#update put:[
-        view update.
-
-        listViews from:(anIndex + 1) do:[:v|
-            (view selectedInstanceType) ~~ #directory ifTrue:[
-                v inspect:nil
-            ] ifFalse:[
-                v inspect:(view selectedInstanceVar).
-                view := v.
-            ]
-        ].
-        self update
-    ].
-
-    (InspectorList isTraceable:inst) ifFalse:[
-        ^ menu
-    ].
-
-    menu  addLabels:#(
-                      '-'
-                      'trace'
-                      'trap'
-                      'untrace / untrap'
-                     )
-          selectors:#(
-                      nil
-                      trace
-                      trap
-                      untrace
-                     ).
-
-    menu actionAt:#untrace put:[self doUntrace:inst].
-
-    args := Array new:2 withAll:inst.
-    lbls := Array with:'message'
-                  with:((Text string:' all ' emphasis:#underline), ' messages').
-
-    menu subMenuAt:#trace put:(
-        PopUpMenu labels:lbls selectors:#(doTrace: doTraceAll:) args:args
-    ).
-
-    menu subMenuAt:#trap put:(
-        PopUpMenu labels:lbls selectors:#(doTrap: doTrapAll:) args:args
-    ).
-
-  ^ menu
-
-
-! !
-
-!InspectorPanelView methodsFor:'private'!
-
-doItOrAccept:aBlock
-    "handle a doIt or accept action; on success all the folloed views are
-     updated
-    "
-    |index list result instVar|
-
-    list    := self findLastValidListWithSelection.
-    result  := aBlock value:list.
-    instVar := list selectedInstanceVar.
-    index   := listViews findLast:[:v|v == list].
-
-    (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:[
-        ^ listViews at:index
-    ].
-
-    leftHistory notEmpty ifTrue:[^ leftHistory last]
-                        ifFalse:[^ listViews at:1]
-!
-
-update
-    "update labels and scrollbar
-    "
-    |pview cview stop index ispObj label|
-
-"UPDATE LABELS
-"
-    index := 1.
-    stop  := listViews size.
-
-    [   cview  := listViews at:index.
-        ispObj := cview inspectedObject.
-        label  := labelViews at:index.
-        index  := index + 1.
-
-        ispObj notNil ifTrue:[
-            label label:(ispObj class name asString).
-            pview := cview.
-        ] ifFalse:[
-            [index <= stop] whileTrue:[
-                (labelViews at:index) label:''.
-                index := index + 1
-            ].
-
-            (pview isNil or:[pview selectedInstanceType == #normal]) ifTrue:[
-                pview notNil ifTrue:[ispObj := pview selectedInstanceVar].
-                label label:ispObj class name asString
-            ] ifFalse:[
-                label label:''
-            ]
-        ].
-        index > stop
-
-    ] whileFalse.
-
-"UPDATE SCROLLBARS
-"
-    index := listViews size + leftHistory size + rightHistory size.
-
-    (listViews last) selectedInstanceType notNil ifTrue:[
-        index := index + 1
-    ].
-    scrollBar thumbHeight:(stop / index) * 100.
-    scrollBar thumbOrigin:(100  / index * leftHistory size).
-
-! !
-
-!InspectorPanelView methodsFor:'private frames'!
-
-computeExtentOfFrames
-    "compute the extent of all frames (origin/corner)
-    "
-    |orig corn offset newX|
-
-    orig := ( 0.0 @ 0.0 ).
-    corn := ( 0.0 @ 1.0 ).
-
-    offset := 1.0 / (frames size).
-    newX   := 0.0.
-
-    frames do:[:frame|
-        (newX := newX + offset) > 1.0 ifTrue:[ newX := 1.0 ].
-        corn  := newX @ corn y.
-        frame origin:orig corner:corn.
-        orig  := newX @ orig y.
-    ].
-
-
-!
-
-createViewWithoutRedraw
-    "add a new view at end of the panel
-    "
-    |view frame label index|
-
-    frame := SimpleView in:hzpView.
-
-    label := Label origin:0.0@0.0 corner:1.0@20 in:frame.
-    label  leftInset:15.
-    label rightInset:2.
-
-    view  := ScrollableView for:InspectorListView miniScroller:true origin:0.0@20 
-                         corner:1.0@1.0 in:frame.
-
-    view := view scrolledView.
-
-    frames add:frame.
-    labelViews add:label.
-    listViews  add:view.
-
-    index := listViews size.
-
-    index == 1 ifTrue:[
-        view includesSelf:true
-    ].
-
-    label adjust:#left.
-    label label:''.
-    label level:1.
-    label menuHolder:self; menuMessage:#labelMenu; menuPerformer:self.
-
-    view action:[:el|self singleClickAt:index].
-
-    view delegate:self.
-    view menuHolder:self; menuMessage:#viewMenu; menuPerformer:self.
-
-! !
-
-!InspectorPanelView methodsFor:'scrolling-basic'!
-
-moveContentsLeft:nTimes
-    "move the contents of all views one position left
-    "
-    |fView stop pView index|
-
-    (nTimes < 1 or:[listViews last isEmpty]) ifTrue:[
-        ^ self
-    ].
-
-    index := nTimes.
-    stop  := (listViews size) - 1.
-    fView := listViews first.
-    pView := listViews at:stop.
-
-
-    [   leftHistory add:(fView list).
-
-        1 to:stop do:[:i|
-            (listViews at:i) list:(listViews at:(i+1))
-        ].
-
-        rightHistory notEmpty ifTrue:[
-            (listViews last) list:(rightHistory removeLast)
-        ] ifFalse:[
-            (listViews last) inspect:(pView selectedInstanceVar)
-        ].
-        ((index := index - 1) == 0 or:[listViews last isEmpty])
-
-    ] whileFalse.
-
-    self update.
-
-
-
-!
-
-moveContentsRight:nTimes
-    "move the contents of all views one position right
-    "
-    |size index lView fView|
-
-    size := leftHistory size.
-
-    (nTimes > 0 and:[size ~~ 0]) ifTrue:[
-        nTimes > size ifFalse:[index := nTimes]
-                       ifTrue:[index := size].
-
-        size  := listViews size.
-        lView := listViews last.
-        fView := listViews first.
-
-        1 to:index do:[:i|
-            lView hasSelection ifTrue:[
-                rightHistory add:(lView list)
-            ].
-            size to:2 by:-1 do:[:i|
-                (listViews at:i) list:(listViews at:(i-1))
-            ].
-            fView list:(leftHistory removeLast)
-        ].
-        self update
-    ]
-
-!
-
-scrollTo:nPercent
-    "set views and contents dependant on scroll bar
-    "
-    |dY no noScr pR|
-
-    noScr := listViews size + leftHistory size + rightHistory size.
-
-    (listViews last) selectedInstanceType notNil ifTrue:[
-        noScr := noScr + 1
-    ].
-    dY := 100 / noScr.
-    pR := nPercent roundTo:dY.
-
-    no := ((dY * leftHistory size) - pR) / dY.
-
-    no == 0 ifTrue:[
-        (nPercent - pR) > 0 ifTrue:[no := -1]
-                           ifFalse:[no :=  1]
-    ].
-    no < 0 ifTrue:[self moveContentsLeft:(no negated)]
-          ifFalse:[self moveContentsRight:no]
-! !
-
-!InspectorPanelView class methodsFor:'documentation'!
-
-version
-    ^ '$Header$'
-! !
--- a/InspectorView.st	Wed Sep 08 12:00:12 1999 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,151 +0,0 @@
-"
- COPYRIGHT (c) 1997 by eXept Software AG
-              All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
-
-
-
-"{ NameSpace: NewInspector }"
-
-VariableVerticalPanel subclass:#InspectorView
-	instanceVariableNames:'inspectorView userSpace workSpace inspectedObject'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Interface-Inspector'
-!
-
-!InspectorView class methodsFor:'documentation'!
-
-copyright
-"
- COPYRIGHT (c) 1997 by eXept Software AG
-              All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
-
-
-!
-
-documentation
-"
-    a new (multipane) inspector;
-    open with:
-        NewInspector::InspectorView inspect:someObject
-
-    install as standard inspector:
-        Smalltalk at:#Inspector put:(NewInspector::InspectorView)
-
-    [open with:]
-        NewInspector::InspectorView 
-                inspect:(Array with:#hello with:'hello' with:#(1 2 3) asSortedCollection with:Display)
-
-    [author:]
-        Claus Atzkern
-"
-!
-
-examples
-
-"
-    open an inspector on an array
-                                                                        [exBegin]
-    |array|
-
-    array := Array new:5.
-    array at:1 put:(Array new:400).
-    NewInspector::InspectorView inspect:array
-                                                                        [exEnd]
-"
-! !
-
-!InspectorView class methodsFor:'instance creation'!
-
-inspect:anObject
-    "start inspector on an instance
-    "
-    ^ self openOn:anObject
-!
-
-openOn:anObject
-    "start an inspector on some object
-    "
-
-    |top isp|
-
-    top := StandardSystemView new extent:600@400.
-    isp := InspectorView origin:0.0@0.0  corner:1.0@1.0 in:top.
-    isp inspect:anObject.
-    top open.
-
-    ^ isp.
-! !
-
-!InspectorView methodsFor:'accessing'!
-
-inspect:anInstance
-
-    inspectedObject := anInstance.
-    self topView label:(inspectedObject class name asString).
-    inspectorView inspect:anInstance.
-    self updateWorkSpace.
-
-! !
-
-!InspectorView methodsFor:'initialization'!
-
-initialize
-    |view wsHeight|
-
-    super initialize.
-
-    view := SimpleView origin:0.0 @ 0.0 corner:1.0 @ 0.5 in:self.
-
-    inspectorView := InspectorPanelView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:view.
-    workSpace     := Workspace          origin:0.0 @ 1.0 corner:1.0 @ 1.0 in:view.
-    userSpace     := Workspace          origin:0.0 @ 0.5 corner:1.0 @ 1.0 in:self.
-
-    wsHeight := (workSpace preferredExtentForLines:1 cols:10) y.
-    workSpace     topInset:wsHeight negated.
-    inspectorView bottomInset:wsHeight.
-
-    userSpace acceptAction:[:theText|inspectorView accept:theText notifying:workSpace].
-    workSpace acceptAction:[:theText|inspectorView accept:theText notifying:workSpace].
-
-    userSpace   doItAction:[:theCode|inspectorView doIt:theCode notifying:workSpace].
-    workSpace   doItAction:[:theCode|inspectorView doIt:theCode notifying:workSpace].
-
-    inspectorView action:[:el|self updateWorkSpace].
-
-    inspectorView valueChangedAction:[:el||lbl|
-        workSpace list:(Array with:(el displayString)).
-    ].
-
-    "Modified: 18.3.1997 / 10:57:34 / cg"
-! !
-
-!InspectorView methodsFor:'update'!
-
-updateWorkSpace
-    "update the workSpace
-    "
-    workSpace list:(Array with:(inspectorView selectedInstanceVar displayString)).
-! !
-
-!InspectorView class methodsFor:'documentation'!
-
-version
-    ^ '$Header$'
-! !
--- a/Make.proto	Wed Sep 08 12:00:12 1999 +0200
+++ b/Make.proto	Wed Sep 08 19:40:37 1999 +0200
@@ -30,10 +30,10 @@
 O=$(O2)
 
 IOBJS=  \
-	InspectorList.$(O)      \
-	InspectorListView.$(O)  \
-	InspectorView.$(O)      \
-	InspectorPanelView.$(O)
+	NewInspectorList.$(O)      \
+	NewInspectorListView.$(O)  \
+	NewInspectorView.$(O)      \
+	NewInspectorPanelView.$(O)
 
 OBJS= \
 	ColorMenu.$(O) \
--- a/NewInspectorList.st	Wed Sep 08 12:00:12 1999 +0200
+++ b/NewInspectorList.st	Wed Sep 08 19:40:37 1999 +0200
@@ -13,14 +13,14 @@
 
 "{ NameSpace: NewInspector }"
 
-Object subclass:#InspectorList
+Object subclass:#NewInspectorList
 	instanceVariableNames:'inspectedObject instanceNames instanceTypes selection'
 	classVariableNames:''
 	poolDictionaries:''
-	category:'Interface-Inspector'
+	category:'Interface-NewInspector'
 !
 
-!InspectorList class methodsFor:'documentation'!
+!NewInspectorList class methodsFor:'documentation'!
 
 copyright
 "
@@ -37,7 +37,7 @@
 
 ! !
 
-!InspectorList class methodsFor:'instance creation'!
+!NewInspectorList class methodsFor:'instance creation'!
 
 for:anObject
     "create a new list for an instance
@@ -54,7 +54,7 @@
 
 ! !
 
-!InspectorList class methodsFor:'helpers'!
+!NewInspectorList class methodsFor:'helpers'!
 
 asString:aCollection
     "converts any collection to a string seperated by spaces. If
@@ -83,7 +83,7 @@
 
 ! !
 
-!InspectorList class methodsFor:'testing'!
+!NewInspectorList class methodsFor:'testing'!
 
 isDirectory:anInstance
     "returns true if the instance is a directory
@@ -129,7 +129,7 @@
 
 ! !
 
-!InspectorList methodsFor:'accessing'!
+!NewInspectorList methodsFor:'accessing'!
 
 includesSelf:aBoolean
     "includes 'self' dependant on the boolean
@@ -194,7 +194,7 @@
     "Modified: / 4.2.1999 / 20:00:38 / cg"
 ! !
 
-!InspectorList methodsFor:'accessing contents'!
+!NewInspectorList methodsFor:'accessing contents'!
 
 inspectedObject
     "returns current inspected object
@@ -253,7 +253,7 @@
 
 ! !
 
-!InspectorList methodsFor:'initialization'!
+!NewInspectorList methodsFor:'initialization'!
 
 initialize
     "initialize instance attributes
@@ -265,7 +265,7 @@
 
 ! !
 
-!InspectorList methodsFor:'private'!
+!NewInspectorList methodsFor:'private'!
 
 resizeTo:aNumber
     "resize list to minimum aNumber
@@ -316,7 +316,7 @@
     ].
 ! !
 
-!InspectorList methodsFor:'selections'!
+!NewInspectorList methodsFor:'selections'!
 
 selectedInstanceType
     "returns type assigned to the selected list entry (#directory #normal #self #grow).
@@ -357,7 +357,7 @@
     ]    
 ! !
 
-!InspectorList methodsFor:'testing'!
+!NewInspectorList methodsFor:'testing'!
 
 includesSelf
     "returns true if 'self' is included in the list
@@ -381,7 +381,7 @@
 
 ! !
 
-!InspectorList methodsFor:'user interaction'!
+!NewInspectorList methodsFor:'user interaction'!
 
 accept:aText notifying:aView
     "evaluating aText on the selected instance var; if an error occurs #Error
@@ -488,7 +488,7 @@
     self update
 ! !
 
-!InspectorList class methodsFor:'documentation'!
+!NewInspectorList class methodsFor:'documentation'!
 
 version
     ^ '$Header$'
--- a/NewInspectorListView.st	Wed Sep 08 12:00:12 1999 +0200
+++ b/NewInspectorListView.st	Wed Sep 08 19:40:37 1999 +0200
@@ -14,14 +14,14 @@
 
 "{ NameSpace: NewInspector }"
 
-SelectionInListView subclass:#InspectorListView
+SelectionInListView subclass:#NewInspectorListView
 	instanceVariableNames:'actionHolder inspectorList includesSelf'
 	classVariableNames:''
 	poolDictionaries:''
-	category:'Interface-Inspector'
+	category:'Interface-NewInspector'
 !
 
-!InspectorListView class methodsFor:'documentation'!
+!NewInspectorListView class methodsFor:'documentation'!
 
 copyright
 "
@@ -62,7 +62,7 @@
 "
 ! !
 
-!InspectorListView methodsFor:'accessing'!
+!NewInspectorListView methodsFor:'accessing'!
 
 includesSelf:aBool
     includesSelf := aBool
@@ -76,7 +76,7 @@
     "set the lists contents from another list
     "
     aList notNil ifTrue:[inspectorList := aList list]
-                ifFalse:[inspectorList := InspectorList new].
+                ifFalse:[inspectorList := NewInspectorList new].
 
     inspectorList includesSelf:includesSelf.
     super list:(inspectorList instanceNames).
@@ -90,7 +90,7 @@
 
 ! !
 
-!InspectorListView methodsFor:'accessing actions'!
+!NewInspectorListView methodsFor:'accessing actions'!
 
 action:aOneArgAction
     "set the single click action block. If non-nil, that one is evaluated on single
@@ -99,7 +99,7 @@
     actionHolder := aOneArgAction
 ! !
 
-!InspectorListView methodsFor:'drawing'!
+!NewInspectorListView methodsFor:'drawing'!
 
 drawVisibleLineSelected:visLineNr with:fg and:bg
     "redraw a single line as selected.
@@ -167,7 +167,7 @@
 
 ! !
 
-!InspectorListView methodsFor:'event handling'!
+!NewInspectorListView methodsFor:'event handling'!
 
 sizeChanged:how
     "redraw marks
@@ -177,7 +177,7 @@
 
 ! !
 
-!InspectorListView methodsFor:'initialization'!
+!NewInspectorListView methodsFor:'initialization'!
 
 initialize
     "initialization
@@ -187,7 +187,7 @@
     ignoreReselect := false.
     includesSelf   := false.
     actionHolder   := [:el|].
-    inspectorList  := InspectorList new.
+    inspectorList  := NewInspectorList new.
 
     actionBlock := [:dummy|
         self setSelection:selection.
@@ -195,7 +195,7 @@
     ].
 ! !
 
-!InspectorListView methodsFor:'private'!
+!NewInspectorListView methodsFor:'private'!
 
 doesNotUnderstand:aMessage
     "forward a message to the inspectorList
@@ -232,7 +232,7 @@
 
 ! !
 
-!InspectorListView methodsFor:'selections'!
+!NewInspectorListView methodsFor:'selections'!
 
 setSelection:aNumberOrNil
     "select line, aNumber or deselect if argument is nil
@@ -245,7 +245,7 @@
                                  ifFalse:[super list:(inspectorList instanceNames)].
 ! !
 
-!InspectorListView methodsFor:'user interaction'!
+!NewInspectorListView methodsFor:'user interaction'!
 
 accept:aText notifying:aView
     "evaluating aText on the selected instance var; if an error occurs #Error
@@ -290,7 +290,7 @@
     super list:(inspectorList instanceNames).
 ! !
 
-!InspectorListView class methodsFor:'documentation'!
+!NewInspectorListView class methodsFor:'documentation'!
 
 version
     ^ '$Header$'
--- a/NewInspectorPanelView.st	Wed Sep 08 12:00:12 1999 +0200
+++ b/NewInspectorPanelView.st	Wed Sep 08 19:40:37 1999 +0200
@@ -14,15 +14,15 @@
 
 "{ NameSpace: NewInspector }"
 
-SimpleView subclass:#InspectorPanelView
+SimpleView subclass:#NewInspectorPanelView
 	instanceVariableNames:'frames labelViews listViews scrollBar maxDepth leftHistory
 		rightHistory hzpView actionBlock valueChangedAction'
 	classVariableNames:''
 	poolDictionaries:''
-	category:'Interface-Inspector'
+	category:'Interface-NewInspector'
 !
 
-!InspectorPanelView class methodsFor:'documentation'!
+!NewInspectorPanelView class methodsFor:'documentation'!
 
 copyright
 "
@@ -49,7 +49,7 @@
     |top slv|
 
     top := StandardSystemView new extent:600@400.
-    slv := NewInspector::InspectorPanelView origin:0.0@0.0 corner:1.0@1.0 in:top.
+    slv := NewInspector::NewInspectorPanelView origin:0.0@0.0 corner:1.0@1.0 in:top.
     slv inspect:top.
     slv action:[:el|Transcript showCR:el].
     top open.
@@ -67,7 +67,7 @@
     top := StandardSystemView new extent:600@400.
     vvp := VariableVerticalPanel origin:0.0@0.0  corner:1.0@1.0 in:top.
 
-    slv := NewInspector::InspectorPanelView origin:0.0@0.0 corner:1.0@0.5 in:vvp.
+    slv := NewInspector::NewInspectorPanelView origin:0.0@0.0 corner:1.0@0.5 in:vvp.
     edt := Workspace origin:0.0 @ 0.5 corner:1.0 @ 1.0 in:vvp.
     edt acceptAction:[:theText|slv accept:theText notifying:edt].
     edt   doItAction:[:theCode|slv doIt:theCode   notifying:edt].
@@ -80,7 +80,7 @@
 "
 ! !
 
-!InspectorPanelView class methodsFor:'constants'!
+!NewInspectorPanelView class methodsFor:'constants'!
 
 minDepth
     "returns the minimum of views assigned to a panel
@@ -88,7 +88,7 @@
     ^ 4
 ! !
 
-!InspectorPanelView methodsFor:'accessing'!
+!NewInspectorPanelView methodsFor:'accessing'!
 
 depth
     "returns number of listViews
@@ -144,7 +144,7 @@
     ]
 ! !
 
-!InspectorPanelView methodsFor:'accessing actions'!
+!NewInspectorPanelView methodsFor:'accessing actions'!
 
 action:aOneArgBlock
     "set the single click action block.
@@ -163,7 +163,7 @@
     valueChangedAction := aOneArgBlock
 ! !
 
-!InspectorPanelView methodsFor:'accessing selections'!
+!NewInspectorPanelView methodsFor:'accessing selections'!
 
 inspectedObject
     "returns the current inspected object
@@ -177,7 +177,7 @@
     ^ self findLastValidListWithSelection selectedInstanceVar
 ! !
 
-!InspectorPanelView methodsFor:'actions'!
+!NewInspectorPanelView methodsFor:'actions'!
 
 accept:aText notifying:aView
     "evaluating aText on the last selected instance var. on success the views
@@ -207,7 +207,7 @@
     self update.
 ! !
 
-!InspectorPanelView methodsFor:'event handling'!
+!NewInspectorPanelView methodsFor:'event handling'!
 
 handlesKeyPress:key inView:someView
     "all keys are handled by this instance itself
@@ -256,7 +256,7 @@
     actionBlock value:sivar.
 ! !
 
-!InspectorPanelView methodsFor:'initializing'!
+!NewInspectorPanelView methodsFor:'initializing'!
 
 initialize
     "initialize instance
@@ -287,7 +287,7 @@
     self depth:maxDepth.
 ! !
 
-!InspectorPanelView methodsFor:'menu - labels & actions'!
+!NewInspectorPanelView methodsFor:'menu - labels & actions'!
 
 browse:anIndex
     self classAtLabel:anIndex do:[:cls| cls browserClass openInClass:cls selector:nil ]
@@ -357,7 +357,7 @@
 
 ! !
 
-!InspectorPanelView methodsFor:'menu - views & actions'!
+!NewInspectorPanelView methodsFor:'menu - views & actions'!
 
 doTrace:anInstance
     "place a trace on messages sent to the instance
@@ -527,7 +527,7 @@
         self update
     ].
 
-    (InspectorList isTraceable:inst) ifFalse:[
+    (NewInspectorList isTraceable:inst) ifFalse:[
         ^ menu
     ].
 
@@ -563,7 +563,7 @@
 
 ! !
 
-!InspectorPanelView methodsFor:'private'!
+!NewInspectorPanelView methodsFor:'private'!
 
 doItOrAccept:aBlock
     "handle a doIt or accept action; on success all the folloed views are
@@ -657,7 +657,7 @@
 
 ! !
 
-!InspectorPanelView methodsFor:'private frames'!
+!NewInspectorPanelView methodsFor:'private frames'!
 
 computeExtentOfFrames
     "compute the extent of all frames (origin/corner)
@@ -691,7 +691,7 @@
     label  leftInset:15.
     label rightInset:2.
 
-    view  := ScrollableView for:InspectorListView miniScroller:true origin:0.0@20 
+    view  := ScrollableView for:NewInspectorListView miniScroller:true origin:0.0@20 
                          corner:1.0@1.0 in:frame.
 
     view := view scrolledView.
@@ -718,7 +718,7 @@
 
 ! !
 
-!InspectorPanelView methodsFor:'scrolling-basic'!
+!NewInspectorPanelView methodsFor:'scrolling-basic'!
 
 moveContentsLeft:nTimes
     "move the contents of all views one position left
@@ -808,7 +808,7 @@
           ifFalse:[self moveContentsRight:no]
 ! !
 
-!InspectorPanelView class methodsFor:'documentation'!
+!NewInspectorPanelView class methodsFor:'documentation'!
 
 version
     ^ '$Header$'
--- a/NewInspectorView.st	Wed Sep 08 12:00:12 1999 +0200
+++ b/NewInspectorView.st	Wed Sep 08 19:40:37 1999 +0200
@@ -14,14 +14,14 @@
 
 "{ NameSpace: NewInspector }"
 
-VariableVerticalPanel subclass:#InspectorView
+VariableVerticalPanel subclass:#NewInspectorView
 	instanceVariableNames:'inspectorView userSpace workSpace inspectedObject'
 	classVariableNames:''
 	poolDictionaries:''
-	category:'Interface-Inspector'
+	category:'Interface-NewInspector'
 !
 
-!InspectorView class methodsFor:'documentation'!
+!NewInspectorView class methodsFor:'documentation'!
 
 copyright
 "
@@ -43,13 +43,13 @@
 "
     a new (multipane) inspector;
     open with:
-        NewInspector::InspectorView inspect:someObject
+        NewInspector::NewInspectorView inspect:someObject
 
     install as standard inspector:
-        Smalltalk at:#Inspector put:(NewInspector::InspectorView)
+        Smalltalk at:#Inspector put:(NewInspector::NewInspectorView)
 
     [open with:]
-        NewInspector::InspectorView 
+        NewInspector::NewInspectorView 
                 inspect:(Array with:#hello with:'hello' with:#(1 2 3) asSortedCollection with:Display)
 
     [author:]
@@ -66,12 +66,12 @@
 
     array := Array new:5.
     array at:1 put:(Array new:400).
-    NewInspector::InspectorView inspect:array
+    NewInspector::NewInspectorView inspect:array
                                                                         [exEnd]
 "
 ! !
 
-!InspectorView class methodsFor:'instance creation'!
+!NewInspectorView class methodsFor:'instance creation'!
 
 inspect:anObject
     "start inspector on an instance
@@ -86,14 +86,14 @@
     |top isp|
 
     top := StandardSystemView new extent:600@400.
-    isp := InspectorView origin:0.0@0.0  corner:1.0@1.0 in:top.
+    isp := NewInspectorView origin:0.0@0.0  corner:1.0@1.0 in:top.
     isp inspect:anObject.
     top open.
 
     ^ isp.
 ! !
 
-!InspectorView methodsFor:'accessing'!
+!NewInspectorView methodsFor:'accessing'!
 
 inspect:anInstance
 
@@ -104,7 +104,7 @@
 
 ! !
 
-!InspectorView methodsFor:'initialization'!
+!NewInspectorView methodsFor:'initialization'!
 
 initialize
     |view wsHeight|
@@ -113,7 +113,7 @@
 
     view := SimpleView origin:0.0 @ 0.0 corner:1.0 @ 0.5 in:self.
 
-    inspectorView := InspectorPanelView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:view.
+    inspectorView := NewInspectorPanelView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:view.
     workSpace     := Workspace          origin:0.0 @ 1.0 corner:1.0 @ 1.0 in:view.
     userSpace     := Workspace          origin:0.0 @ 0.5 corner:1.0 @ 1.0 in:self.
 
@@ -136,7 +136,7 @@
     "Modified: 18.3.1997 / 10:57:34 / cg"
 ! !
 
-!InspectorView methodsFor:'update'!
+!NewInspectorView methodsFor:'update'!
 
 updateWorkSpace
     "update the workSpace
@@ -144,7 +144,7 @@
     workSpace list:(Array with:(inspectorView selectedInstanceVar displayString)).
 ! !
 
-!InspectorView class methodsFor:'documentation'!
+!NewInspectorView class methodsFor:'documentation'!
 
 version
     ^ '$Header$'