optimize widthOfContents and drawing
authorca
Wed, 08 Apr 1998 09:04:19 +0200
changeset 846 368acc8d9258
parent 845 99376de4a566
child 847 8395a2d05464
optimize widthOfContents and drawing
SelTreeV.st
SelectionInTreeView.st
--- a/SelTreeV.st	Wed Apr 08 07:35:02 1998 +0200
+++ b/SelTreeV.st	Wed Apr 08 09:04:19 1998 +0200
@@ -12,15 +12,15 @@
 
 
 SelectionInListView subclass:#SelectionInTreeView
-	instanceVariableNames:'validateDoubleClickBlock selectionHolder rootHolder imageWidth
-		showLines listOfNodes imageInset textInset labelOffsetY lineMask
-		lineColor computeResources showRoot showDirectoryIndicator
-		closeIndicator openIndicator showDirectoryIndicatorForRoot
-		imageOpened imageClosed imageItem discardMotionEvents
-		registeredImages supportsExpandAll'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Views-Text'
+        instanceVariableNames:'validateDoubleClickBlock selectionHolder rootHolder imageWidth
+                showLines listOfNodes imageInset textInset labelOffsetY lineMask
+                lineColor computeResources showRoot showDirectoryIndicator
+                closeIndicator openIndicator showDirectoryIndicatorForRoot
+                imageOpened imageClosed imageItem discardMotionEvents
+                registeredImages supportsExpandAll'
+        classVariableNames:''
+        poolDictionaries:''
+        category:'Views-Text'
 !
 
 !SelectionInTreeView class methodsFor:'documentation'!
@@ -403,17 +403,20 @@
 !
 
 imageOnDevice:anImage
-    "associate iamge to device and clear pixel mask (in case of realized);
+    "associate image to device and clear pixel mask (in case of realized);
      returns the new image.
     "
     |img|
 
-    img := anImage onDevice:device.
+    img := anImage.
 
-    realized ifTrue:[
-        img := img clearMaskedPixels
+    img device ~~ device ifTrue:[
+        img := img copy.
     ].
-    ^ img
+    img := img on:device.
+    img := img clearMaskedPixels.
+  ^ img
+
 !
 
 imageOpened
@@ -451,14 +454,11 @@
 
             (idx := self indexOfNode:aModel) ~~ 0 ifTrue:[
                 something == #value ifTrue:[  
-                    list at:idx put:(aModel name).
-                    self redrawLine:idx.
-                    ^ self
+                    ^ self redrawLine:idx.
                 ].
 
                 something == #indication ifTrue:[
-                    self redrawIndicatorLine:idx.
-                    ^ self
+                    ^ self redrawIndicatorLine:idx.
                 ].
             ].
             ^ self
@@ -501,6 +501,15 @@
 drawVisibleLine:visLineNr from:startCol with:fg and:bg
     self drawFromVisibleLine:visLineNr to:visLineNr with:fg and:bg
 
+!
+
+redrawFromVisibleLine:startVisLineNr to:endVisLineNr
+    self redrawX:0
+               y:(self yOfVisibleLine:startVisLineNr)
+           width:width
+          height:(endVisLineNr - startVisLineNr + 1 * fontHeight)
+
+
 ! !
 
 !SelectionInTreeView methodsFor:'drawing basics'!
@@ -542,7 +551,6 @@
     |node ext img visLn
      x  "{ Class:SmallInteger }"
      y  "{ Class:SmallInteger }"
-     lv "{ Class:SmallInteger }"
      dX "{ Class:SmallInteger }"
     |
 
@@ -555,12 +563,12 @@
 
     node := listOfNodes at:aLineNr.
 
-    ((lv := node level) ~~ 1 or:[showDirectoryIndicatorForRoot]) ifFalse:[
+    (node parent notNil or:[showDirectoryIndicatorForRoot]) ifFalse:[
         ^ self
     ].
 
-    (x := imageWidth // 2) odd ifTrue:[x := x + 1].
-    x := (self xOfFigureLevel:(lv - 1)) + x.
+    x := imageWidth // 2.
+    x := x + (self xOfFigureLevel:(node level - 1)).
 
     "/ draw directory indicator
 
@@ -583,135 +591,139 @@
 redrawLinesX:x0 y:y0 toX:x1 start:start stop:stop
     "redraw from line to line without clearing the background
     "
-    |node image extent isSelected defLineColor rnode prnt
-     x       "{ Class:SmallInteger }"
-     y       "{ Class:SmallInteger }"
-     level   "{ Class:SmallInteger }"
-     yTop    "{ Class:SmallInteger }"
-     yBot    "{ Class:SmallInteger }"
-     yCtr    "{ Class:SmallInteger }"
-     size    "{ Class:SmallInteger }"
-     end     "{ Class:SmallInteger }"
-     index   "{ Class:SmallInteger }"
-     xCross  "{ Class:SmallInteger }"
-     xFig    "{ Class:SmallInteger }"
-     xStr    "{ Class:SmallInteger }"
-     dyLvl   "{ Class:SmallInteger }"
-     soVDt   "{ Class:SmallInteger }"
-     soVLn   "{ Class:SmallInteger }"
-     lv      "{ Class:SmallInteger }"
-     figWidthDiv2 "{ Class:SmallInteger }"
+    |node prevNode parent icon isSelected p1 p2 indicatorExt
+
+     showIndicator
+     showVLines
+     showHLine
+     showIcon
+     showText
+
+     x        "{ Class:SmallInteger }"
+     y        "{ Class:SmallInteger }"
+     end      "{ Class:SmallInteger }"
+     level    "{ Class:SmallInteger }"
+     figDiv2  "{ Class:SmallInteger }"
+
+     yTop     "{ Class:SmallInteger }"
+     yBot     "{ Class:SmallInteger }"
+     yCtr     "{ Class:SmallInteger }"
+
+     xCross   "{ Class:SmallInteger }"
+     xIcon    "{ Class:SmallInteger }"
+     xText    "{ Class:SmallInteger }"
+
+     soVDt    "{ Class:SmallInteger }"
+
+     widthLvl "{ Class:SmallInteger }"
+     insetTxt "{ Class:SmallInteger }"
+     xOfLvl1  "{ Class:SmallInteger }"
     |
-    size         := listOfNodes size.
-    index        := start.
-    end          := stop min:size.
-    level        := -1. "/ to force evaluation of #ifFalse in loop
-    soVDt        := 0.
-    yTop         := y0.
-    yCtr         := yTop - (fontHeight // 2).
-    dyLvl        := imageInset + imageWidth.
-    figWidthDiv2 := imageWidth // 2.
-    figWidthDiv2 odd ifTrue:[figWidthDiv2 := figWidthDiv2 + 1].
+    end      := stop min:(listOfNodes size).
+    yBot     := y0.
+    yCtr     := yBot - (fontHeight // 2).
+    widthLvl := imageInset + imageWidth.
+    insetTxt := imageWidth + textInset.
+    figDiv2  := imageWidth // 2.
+    xOfLvl1  := self xOfFigureLevel:1.
+
+    showDirectoryIndicator ifTrue:[
+        indicatorExt := openIndicator extent // 2.
+    ].
 
     showLines ifTrue:[
-        soVDt := (figWidthDiv2 + (self xOfFigureLevel:1)) - dyLvl - dyLvl.
         self setMaskOrigin:(self viewOrigin + (0 @ 1) \\ (lineMask extent)).
-        defLineColor := lineColor ? fgColor.
     ].
 
-    [index <= end] whileTrue:[
-        node := listOfNodes at:index.
-        yBot := yTop + fontHeight.
+    parent   := 4711.                           "/ to force a recompute
+    prevNode := 4711.                           "/ to force a recomputation of the level
+
+    start to:end do:[:anIndex|
+        node := listOfNodes at:anIndex.
+        yTop := yBot - 1.
+        yBot := yBot + fontHeight.
         yCtr := yCtr + fontHeight.
 
-        (lv := node level) == level ifFalse:[
-            xFig   := self xOfFigureLevel:lv.
-            xStr   := self xOfStringLevel:lv.
-            xCross := xFig - dyLvl + figWidthDiv2.
-            level  := lv.
-            soVLn  := lv * dyLvl + soVDt.
+        parent ~~ node parent ifTrue:[
+            parent := node parent.
+
+            prevNode == parent ifTrue:[
+                level := level + 1.
+                xIcon := xIcon + widthLvl.
+            ] ifFalse:[
+                level := node level.
+                xIcon := level - 1 * widthLvl + xOfLvl1.
+            ].
+            xText  := xIcon + insetTxt.
+            xCross := xIcon - widthLvl + figDiv2.
+
+            showIndicator := (     showDirectoryIndicator
+                              and:[(parent notNil or:[showDirectoryIndicatorForRoot])
+                              and:[(xCross + indicatorExt x > x0 and:[(xCross - indicatorExt x) < x1])]]
+                             ).
+            showIcon      := xIcon < x1 and:[xText > x0].
+            showText      := xText < x1.
+
+            showLines ifTrue:[
+                showVLines := xCross >= x0 and:[parent notNil].
+                showHLine  := (     xIcon > x0
+                                and:[(parent notNil
+                                 or:[showDirectoryIndicatorForRoot and:[showDirectoryIndicator]])]
+                              ).
+            ].
         ].
 
-        (isSelected := self isInSelection:index) ifTrue:[
+        (isSelected := self isInSelection:anIndex) ifTrue:[
             self paint:hilightFgColor on:hilightBgColor
         ].
         showLines ifTrue:[
             isSelected ifFalse:[
-                self paint:defLineColor on:bgColor
+                self paint:lineColor on:bgColor
             ].
             self mask:lineMask.
 
             xCross < x1 ifTrue:[
-                (    ((x := xFig + figWidthDiv2) between:x0 and:x1)
+                (    ((x := xIcon + figDiv2) between:x0 and:x1)
                  and:[node isCollapsable
                  and:[node children notEmpty]]
                 ) ifTrue:[
                     self displayLineFromX:x y:yCtr toX:x y:yBot
                 ].
 
-                "/ vertical line from previous to current form
-                (xCross >= x0 and:[level ~~ 1]) ifTrue:[
-                    prnt := node parent children.
-                    prnt isEmpty ifTrue:[ ^ self ]. "/ error occured
-                    lv := prnt last == node ifTrue:[yCtr] ifFalse:[yBot].
-                    self displayLineFromX:xCross y:yTop - 1 toX:xCross y:lv
-                ].
-
-                "/ horizontal line from previous to current form
-                (     xFig > x0
-                 and:[(level ~~ 1
-                  or:[showDirectoryIndicatorForRoot and:[showDirectoryIndicator]])]
-                ) ifTrue:[
-                    self displayLineFromX:xCross y:yCtr toX:xFig y:yCtr
+                showHLine ifTrue:[
+                    self displayLineFromX:xCross y:yCtr toX:x y:yCtr
                 ]
             ].
 
-        "/  draw all vertical lines to left side
-            (xCross >= x0 and:[(rnode := node parent) notNil]) ifTrue:[
-                x := soVLn.
-                y := yTop - 1.
+            showVLines ifTrue:[
+                y := parent basicLastChild == node ifTrue:[yCtr] ifFalse:[yBot].
+                self displayLineFromX:xCross y:yTop toX:xCross y:y.
 
-                [((prnt := rnode parent) notNil and:[(x := x - dyLvl) >= x0])] whileTrue:[
-                    (prnt children last ~~ rnode and:[x <= x1]) ifTrue:[
-                        self displayLineFromX:x y:y toX:x y:yBot
+                x  := xCross.
+                p2 := parent.
+
+                [((p1 := p2 parent) notNil and:[(x := x - widthLvl) >= x0])] whileTrue:[
+                    (p1 basicLastChild ~~ p2 and:[x <= x1]) ifTrue:[
+                        self displayLineFromX:x y:yTop toX:x y:yBot
                     ].
-                    rnode := prnt
+                    p2 := p1
                 ]
             ].
             self mask:nil.
         ].
-        isSelected ifFalse:[
-            self paint:fgColor on:bgColor
-        ].
 
-        "/ draw image
-        (image := self figureFor:node) notNil ifTrue:[
-            (xFig < x1 and:[xStr > x0]) ifTrue:[
-                self displayForm:image x:xFig y:(yCtr - (image height // 2))
-            ]
-        ].
-
-        "/ draw text label
-        xStr < x1 ifTrue:[
-            self drawLabelIndex:index atX:xStr y:yCtr .
+        (showIcon and:[(icon := self figureFor:node) notNil]) ifTrue:[
+            self displayForm:icon x:xIcon y:(yCtr - (icon height // 2))
         ].
-
-        "/ draw directory indicator
-
-        (showDirectoryIndicator and:[node showIndicator]) ifTrue:[
-            (level ~~ 1 or:[showDirectoryIndicatorForRoot]) ifTrue:[
-                image  := node isCollapsable ifTrue:[openIndicator] ifFalse:[closeIndicator].
-                extent := image extent // 2.
-                x := extent x.
-
-                (xCross + x > x0 and:[(x := xCross - x) < x1]) ifTrue:[
-                    self displayForm:image x:x y:(yCtr - extent y)
-                ]
-            ]
+        showText ifTrue:[
+            isSelected ifFalse:[ self paint:fgColor on:bgColor ].
+            self drawLabelIndex:anIndex atX:xText y:yCtr .
         ].
-        "/ setup next line
-        index := index + 1.
-        yTop  := yBot.
+        (showIndicator and:[node showIndicator]) ifTrue:[
+            icon := node isCollapsable ifTrue:[openIndicator] ifFalse:[closeIndicator].
+            self displayForm:icon x:(xCross - indicatorExt x) y:(yCtr - indicatorExt y)
+        ].
+        prevNode := node.
     ]
 
 !
@@ -728,8 +740,6 @@
      x   "{ Class: SmallInteger }" 
     |
 
-    aList size == 0 ifTrue:[ ^ self ].
-
     strikeOut ifTrue:[
         y := fontHeight // 2.
         self paint:bgColor.
@@ -746,7 +756,7 @@
             aList do:[:sY|
                 y := sY - spc. self displayLineFromX:x0 y:y toX:x1 y:y.
                 y := y  + dY.  self displayLineFromX:x0 y:y toX:x1 y:y.
-            ]
+            ].
         ]
     ] ifFalse:[
         hilightStyle == #motif ifTrue:[
@@ -814,7 +824,7 @@
 buttonPress:button x:x y:y
     "check for indicator
     "
-    |expand node lineNr isExpandable|
+    |expand node lineNr sensor what|
 
     lineNr := self indicatiorLineForButton:button atX:x y:y.
 
@@ -823,10 +833,6 @@
     ].
     node := listOfNodes at:lineNr.
 
-    node hasChildren ifFalse:[                  "/ no children exists
-        ^ super buttonPress:button x:x y:y
-    ].
-
     discardMotionEvents := true.
     dragIsActive  := false.
     clickPosition := nil.
@@ -838,40 +844,14 @@
             self selection:nil
         ]
     ].
-    isExpandable := node isExpandable.
-
-    self isCtrlMetaAltOrShiftPressed ifFalse:[
-        ^ self nodeAt:lineNr expand:isExpandable
-    ].
+    sensor := self sensor.
 
-    isExpandable ifTrue:[
-        supportsExpandAll ifFalse:[
-            ^ self nodeAt:lineNr expand:isExpandable
-        ].
-        node expandAll
+    (sensor notNil and:[(sensor ctrlDown or:[sensor shiftDown])]) ifTrue:[
+        what := nil
     ] ifFalse:[
-        (node hasExpandedChildren) ifTrue:[
-            node hasChildrenWithSubChildren ifFalse:[
-                ^ self nodeAt:lineNr expand:isExpandable
-            ].
-            node collapseAllChildren
-        ] ifFalse:[
-            supportsExpandAll ifFalse:[
-                ^ self nodeAt:lineNr expand:isExpandable
-            ].
-            node expandAllChildren
-        ]
+        what := node isExpandable
     ].
-
-    node children isEmpty ifTrue:[
-     "/ no children; redraw selected line (image might change)
-        self redrawLine:lineNr.
-    ] ifFalse:[
-     "/ with children; update list and redraw to end.
-        self recomputeListFromNodeAt:lineNr
-    ]
-
-
+    self nodeAt:lineNr expand:what
 !
 
 buttonRelease:button x:x y:y
@@ -905,7 +885,7 @@
 indicatiorLineForButton:aButton atX:x y:y
     "returns linenumber assigned to indicator at x/y or 0
     "
-    |nr x0 node|
+    |sensor nr x0 node|
 
     (     enabled
      and:[showDirectoryIndicator
@@ -925,7 +905,6 @@
         ]
     ].            
     ^ 0
-
 !
 
 isCtrlMetaAltOrShiftPressed
@@ -1055,7 +1034,6 @@
     self redrawSelFrameForYs:sel fromX:x toX:maxX.
 
     self clippingRectangle:savClip.
-
 ! !
 
 !SelectionInTreeView methodsFor:'initialization'!
@@ -1064,9 +1042,8 @@
     super create.
     lineMask := lineMask onDevice:device.
 
-    lineColor notNil ifTrue:[
-        lineColor := lineColor onDevice:device
-    ]
+    lineColor := lineColor isNil ifTrue:[fgColor]
+                                ifFalse:[lineColor onDevice:device].
 !
 
 destroy
@@ -1105,7 +1082,7 @@
     |img x y keysAndIcons|
 
     imageOpened isNil ifTrue:[
-        imageOpened := (self class imageOpened) onDevice:device
+        imageOpened := self imageOnDevice:(self class imageOpened)
     ].
 
     imageClosed isNil ifTrue:[
@@ -1125,7 +1102,7 @@
     (keysAndIcons := self fetchDefaultImages) notNil ifTrue:[
         keysAndIcons keysAndValuesDo:[:aKey :anIcon|
             (anIcon isImage and:[aKey notNil]) ifTrue:[
-                registeredImages at:aKey put:(self imageOnDevice:anIcon copy)
+                registeredImages at:aKey put:(self imageOnDevice:anIcon)
             ]
         ]
     ].
@@ -1172,6 +1149,7 @@
     imageInset := 0.    "/ set during indication enabled
     imageWidth := 8.    "/ default: will change during startup
     self model:nil.     "/ creates a default model.
+
 !
 
 realize
@@ -1223,8 +1201,12 @@
         fontHeight odd ifTrue:[
             fontHeight := fontHeight + 1
         ].
+        "/ round and not odd: because of line drawing
 
-        imageWidth := extent x.
+        imageWidth := (extent x) // 2.
+        imageWidth odd ifTrue:[imageWidth := imageWidth + 1].
+        imageWidth := imageWidth * 2.
+
         self recomputeDirectoryIndicator.
         self computeNumberOfLinesShown.
     ]
@@ -1243,30 +1225,11 @@
     "get list from model and return the new list.
      If listMessage is nil, try aspectMessage for backward compatibilty.
     "
-    |msg list
-     runs "{ Class: SmallInteger }"
-     idx  "{ Class: SmallInteger }"
-    |
-    widthOfWidestLine := nil.
-
-    (msg := listMsg ? aspectMsg) notNil ifTrue:[
-        listOfNodes := model perform:msg.
+    |msg|
 
-        (runs := listOfNodes size) ~~ 0 ifTrue:[
-            self refetchDeviceResources.
-            idx  := 1.
-            list := OrderedCollection new:runs.
-
-            runs timesRepeat:[
-                list add:(listOfNodes at:idx) name.
-                idx := idx + 1.
-            ].
-            ^ list
-        ]
-    ].
-    listOfNodes := #().
-  ^ #()
-
+    widthOfWidestLine := nil.
+    listOfNodes := (msg := listMsg ? aspectMsg) notNil ifTrue:[model perform:msg] ifFalse:[#()].
+  ^ listOfNodes
 !
 
 model:aModel
@@ -1363,52 +1326,45 @@
     "
     |list time|
 
-    list := aList.
+    list := (aList size == 0) ifTrue:[#()] ifFalse:[aList].
+    super list:list keepSelection:keepSelection.
+    self refetchDeviceResources.
 
-    list size == 0 ifTrue:[
-        listOfNodes := #()
-    ] ifFalse:[
-        (list first respondsTo:#hasChildren) ifTrue:[
-            listOfNodes := aList.
-            self refetchDeviceResources.
-            list := listOfNodes collect:[:aNode| aNode name ].
-        ]
-    ].
-    super list:list keepSelection:keepSelection
 !
 
 nodeAt:anIndex expand:doExpand
     "expand or collapse the node at an index, anIndex dependent on the boolean state
      of doExpand
     "
-    |node|
+    |node isExpandable|
 
     node := listOfNodes at:anIndex.
+    isExpandable := node isExpandable.
 
-    node hasChildren ifFalse:[          "/ no children exists
-        ^ self
-    ].
-    node isExpandable ifTrue:[
-        doExpand ifFalse:[^ self].      "/ already expanded
-        node expand
+    isExpandable == doExpand ifTrue:[
+        isExpandable ifTrue:[node expand]
+                    ifFalse:[node collapse]
     ] ifFalse:[
-        doExpand ifTrue:[^ self].       "/ already collapsed
-        node collapse
+        doExpand notNil ifTrue:[
+            ^ self
+        ].
+        node hasExpandedChildren ifTrue:[
+            node collapseAll.
+            node expand.
+        ] ifFalse:[
+            node expandAll
+        ]
     ].
 
     node children isEmpty ifTrue:[
-     "/ no children; redraw selected line (image might change)
-        self redrawLine:anIndex.
-    ] ifFalse:[
-     "/ with children; update list and redraw to end.
-        self recomputeListFromNodeAt:anIndex
-    ]
-
-
-!
-
-recomputeListFromNodeAt:anIndex
-
+        "/
+        "/ no children; redraw selected line (icon might change)
+        "/
+        ^ self redrawLine:anIndex
+    ].
+    "/
+    "/ list of nodes has changed; recompute list and redraw from index to end
+    "/
     model removeDependent:self.
     model recomputeList.
     model addDependent:self.
@@ -1434,7 +1390,7 @@
         node := listOfNodes at:nr.
         dObj := self dragObjectForNode:node.
         dObj theObject:(node contents).
-        dLbl := LabelAndIcon icon:(self figureFor:node) string:(list at:nr).
+        dLbl := LabelAndIcon icon:(self figureFor:node) string:(node name).
         dObj displayObject:dLbl.
         dObj
     ].
@@ -1443,7 +1399,8 @@
         converted := OrderedCollection new.
         collection keysAndValuesDo:[:nr :obj | 
             (dObj := dragObjectConverter value:obj) notNil ifTrue:[
-                dLbl := LabelAndIcon icon:(self figureFor:(listOfNodes at:nr)) string:(list at:nr).
+                node := listOfNodes at:nr.
+                dLbl := LabelAndIcon icon:(self figureFor:node) string:(node name).
                 converted displayObject:dLbl.
                 converted add:dObj
             ]
@@ -1481,78 +1438,77 @@
 lengthOfLongestLineBetween:firstLine and:lastLine
     "return the length (in characters) of the longest line in a line-range
     "
-    |max|
-
-    max := self widthOfContents:firstLine and:lastLine.
-  ^ (max // fontWidth) + 1
+    ^ self widthOfContents // fontWidth + 1
 !
 
 widthOfContents
     "return the width of the contents in pixels
      - used for scrollbar interface"
 
-    list isNil ifTrue:[^ 0].
+    listOfNodes isNil ifTrue:[^ 0].
 
     (widthOfWidestLine isNil or:[widthOfWidestLine == 0]) ifTrue:[
-        widthOfWidestLine := self widthOfContents:1 and:(self size).
+        widthOfWidestLine := self widthOfLongestLine
     ].
   ^ widthOfWidestLine + (leftMargin * 2)
 
 !
 
-widthOfContents:firstLine and:lastLine
-    "return the length (in pixels) of the longest line in a line-range
+widthOfLongestLine
+    "return the width of the longest line in pixels
     "
-    |parent name item tmpValue
-     max      "{ Class: SmallInteger }"
-     index    "{ Class: SmallInteger }"
-     runs     "{ Class: SmallInteger }"
+    |parent array pItem
+     startX   "{ Class: SmallInteger }"
+     deltaX   "{ Class: SmallInteger }"
      level    "{ Class: SmallInteger }"
-     xOfStr   "{ Class: SmallInteger }"
-     dltX     "{ Class: SmallInteger }"
      width    "{ Class: SmallInteger }"
-     newSz    "{ Class: SmallInteger }"
      maxSz    "{ Class: SmallInteger }"|
 
-    (    (listOfNodes size == 0)
-     or:[(runs := lastLine min:(listOfNodes size)) < firstLine]
-    ) ifTrue:[
-        ^ 0
-    ].
-
+    array  := Array new:30 withAll:0.
+    parent := nil.
+    maxSz  := 1.
     level  := 1.
-    xOfStr := self xOfStringLevel:level.
-    max    := xOfStr.
-    dltX   := imageInset + imageWidth.
-    width  := '1' widthOn:self.
-    parent := 4711.    "/ to force a computation
-    index  := firstLine.
-    runs   := runs - index + 1.
+
+    listOfNodes do:[:anItem|
+        anItem parent ~~ parent ifTrue:[
+            array at:level put:maxSz.
+
+            (parent := anItem parent) == pItem ifTrue:[level := level + 1]
+                                              ifFalse:[level := anItem level].
+            maxSz := array at:level.
+        ].
+        pItem := anItem.
+        maxSz := maxSz max:(anItem name size).
+    ].
+    array at:level put:maxSz.
 
-    runs timesRepeat:[
-        item  := listOfNodes at:index.
-        name  := item name.
-        index := index + 1.
+    startX := self xOfStringLevel:1.
+    deltaX := imageInset + imageWidth.
+    width  := '1' widthOn:self.
+    maxSz  := 0.
 
-        (newSz := name size) ~~ 0 ifTrue:[
-            item parent ~~ parent ifTrue:[
-                parent   := item parent.
-                tmpValue := item level.
-                xOfStr   := xOfStr + ((tmpValue - level) * dltX).
-                level    := tmpValue.
-                maxSz    := 0.
-            ].
-            maxSz < newSz ifTrue:[
-                maxSz := newSz.
-                max   := max max:(xOfStr + (maxSz * width)).
-            ]
-        ]
+    array do:[:el|
+        el == 0 ifTrue:[ ^ maxSz + leftOffset ].
+        maxSz  := maxSz max:(el * width + startX).
+        startX := startX + deltaX.
     ].
-    ^ max + leftOffset.
+! !
+
+!SelectionInTreeView methodsFor:'private redefinitions'!
+
+expandTabs
+    "nothing to do
+    "
 
 
 !
 
+list:aCollection expandTabs:expand scanForNonStrings:scan
+
+    includesNonStrings := false.
+    self list:aCollection expandTabs:false scanForNonStrings:false includesNonStrings:false
+!
+
 withoutRedrawAt:anIndex put:aString
     "change a line without redisplay"
 
@@ -1560,15 +1516,16 @@
 
     width := widthOfWidestLine.
     widthOfWidestLine := nil.
-
     super withoutRedrawAt:anIndex put:aString.
+    widthOfWidestLine := width.
 
-    (widthOfWidestLine := width) notNil ifTrue:[
-        width := self widthOfContents:anIndex and:anIndex.
+    (widthOfWidestLine notNil and:[aString size ~~ 0]) ifTrue:[
+        width := self xOfStringNode:(listOfNodes at:anIndex)
+               + (aString widthOn:self)
+               + leftOffset.
+
         widthOfWidestLine := widthOfWidestLine max:width.
     ].
-
-
 ! !
 
 !SelectionInTreeView methodsFor:'queries'!
@@ -1585,18 +1542,17 @@
             ^ img
         ].
         icon isImage ifTrue:[
-            img := self imageOnDevice:(icon copy).
+            img := self imageOnDevice:icon.
             registeredImages at:icon put:img.
           ^ img
         ]
     ].
 
-    "/ fallback solution
+    aNode hasChildren ifFalse:[
+        ^ imageItem
+    ].
+    ^ aNode hidden ifTrue:[imageClosed] ifFalse:[imageOpened]
 
-    aNode hasChildren ifTrue:[
-        ^ aNode isExpandable ifTrue:[imageClosed] ifFalse:[imageOpened]
-    ].
-  ^ imageItem
 !
 
 indexOfNode:aNode
@@ -1818,7 +1774,9 @@
     |index|
 
     (index := self selectedIndex) ~~ 0 ifTrue:[
-        self nodeAt:index expand:doExpand
+        (listOfNodes at:index) hasChildren ifTrue:[
+            self nodeAt:index expand:doExpand
+        ]
     ].
 
 !
@@ -1834,5 +1792,5 @@
 !SelectionInTreeView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/Attic/SelTreeV.st,v 1.53 1998-04-04 08:45:17 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/Attic/SelTreeV.st,v 1.54 1998-04-08 07:04:19 ca Exp $'
 ! !
--- a/SelectionInTreeView.st	Wed Apr 08 07:35:02 1998 +0200
+++ b/SelectionInTreeView.st	Wed Apr 08 09:04:19 1998 +0200
@@ -12,15 +12,15 @@
 
 
 SelectionInListView subclass:#SelectionInTreeView
-	instanceVariableNames:'validateDoubleClickBlock selectionHolder rootHolder imageWidth
-		showLines listOfNodes imageInset textInset labelOffsetY lineMask
-		lineColor computeResources showRoot showDirectoryIndicator
-		closeIndicator openIndicator showDirectoryIndicatorForRoot
-		imageOpened imageClosed imageItem discardMotionEvents
-		registeredImages supportsExpandAll'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Views-Text'
+        instanceVariableNames:'validateDoubleClickBlock selectionHolder rootHolder imageWidth
+                showLines listOfNodes imageInset textInset labelOffsetY lineMask
+                lineColor computeResources showRoot showDirectoryIndicator
+                closeIndicator openIndicator showDirectoryIndicatorForRoot
+                imageOpened imageClosed imageItem discardMotionEvents
+                registeredImages supportsExpandAll'
+        classVariableNames:''
+        poolDictionaries:''
+        category:'Views-Text'
 !
 
 !SelectionInTreeView class methodsFor:'documentation'!
@@ -403,17 +403,20 @@
 !
 
 imageOnDevice:anImage
-    "associate iamge to device and clear pixel mask (in case of realized);
+    "associate image to device and clear pixel mask (in case of realized);
      returns the new image.
     "
     |img|
 
-    img := anImage onDevice:device.
+    img := anImage.
 
-    realized ifTrue:[
-        img := img clearMaskedPixels
+    img device ~~ device ifTrue:[
+        img := img copy.
     ].
-    ^ img
+    img := img on:device.
+    img := img clearMaskedPixels.
+  ^ img
+
 !
 
 imageOpened
@@ -451,14 +454,11 @@
 
             (idx := self indexOfNode:aModel) ~~ 0 ifTrue:[
                 something == #value ifTrue:[  
-                    list at:idx put:(aModel name).
-                    self redrawLine:idx.
-                    ^ self
+                    ^ self redrawLine:idx.
                 ].
 
                 something == #indication ifTrue:[
-                    self redrawIndicatorLine:idx.
-                    ^ self
+                    ^ self redrawIndicatorLine:idx.
                 ].
             ].
             ^ self
@@ -501,6 +501,15 @@
 drawVisibleLine:visLineNr from:startCol with:fg and:bg
     self drawFromVisibleLine:visLineNr to:visLineNr with:fg and:bg
 
+!
+
+redrawFromVisibleLine:startVisLineNr to:endVisLineNr
+    self redrawX:0
+               y:(self yOfVisibleLine:startVisLineNr)
+           width:width
+          height:(endVisLineNr - startVisLineNr + 1 * fontHeight)
+
+
 ! !
 
 !SelectionInTreeView methodsFor:'drawing basics'!
@@ -542,7 +551,6 @@
     |node ext img visLn
      x  "{ Class:SmallInteger }"
      y  "{ Class:SmallInteger }"
-     lv "{ Class:SmallInteger }"
      dX "{ Class:SmallInteger }"
     |
 
@@ -555,12 +563,12 @@
 
     node := listOfNodes at:aLineNr.
 
-    ((lv := node level) ~~ 1 or:[showDirectoryIndicatorForRoot]) ifFalse:[
+    (node parent notNil or:[showDirectoryIndicatorForRoot]) ifFalse:[
         ^ self
     ].
 
-    (x := imageWidth // 2) odd ifTrue:[x := x + 1].
-    x := (self xOfFigureLevel:(lv - 1)) + x.
+    x := imageWidth // 2.
+    x := x + (self xOfFigureLevel:(node level - 1)).
 
     "/ draw directory indicator
 
@@ -583,135 +591,139 @@
 redrawLinesX:x0 y:y0 toX:x1 start:start stop:stop
     "redraw from line to line without clearing the background
     "
-    |node image extent isSelected defLineColor rnode prnt
-     x       "{ Class:SmallInteger }"
-     y       "{ Class:SmallInteger }"
-     level   "{ Class:SmallInteger }"
-     yTop    "{ Class:SmallInteger }"
-     yBot    "{ Class:SmallInteger }"
-     yCtr    "{ Class:SmallInteger }"
-     size    "{ Class:SmallInteger }"
-     end     "{ Class:SmallInteger }"
-     index   "{ Class:SmallInteger }"
-     xCross  "{ Class:SmallInteger }"
-     xFig    "{ Class:SmallInteger }"
-     xStr    "{ Class:SmallInteger }"
-     dyLvl   "{ Class:SmallInteger }"
-     soVDt   "{ Class:SmallInteger }"
-     soVLn   "{ Class:SmallInteger }"
-     lv      "{ Class:SmallInteger }"
-     figWidthDiv2 "{ Class:SmallInteger }"
+    |node prevNode parent icon isSelected p1 p2 indicatorExt
+
+     showIndicator
+     showVLines
+     showHLine
+     showIcon
+     showText
+
+     x        "{ Class:SmallInteger }"
+     y        "{ Class:SmallInteger }"
+     end      "{ Class:SmallInteger }"
+     level    "{ Class:SmallInteger }"
+     figDiv2  "{ Class:SmallInteger }"
+
+     yTop     "{ Class:SmallInteger }"
+     yBot     "{ Class:SmallInteger }"
+     yCtr     "{ Class:SmallInteger }"
+
+     xCross   "{ Class:SmallInteger }"
+     xIcon    "{ Class:SmallInteger }"
+     xText    "{ Class:SmallInteger }"
+
+     soVDt    "{ Class:SmallInteger }"
+
+     widthLvl "{ Class:SmallInteger }"
+     insetTxt "{ Class:SmallInteger }"
+     xOfLvl1  "{ Class:SmallInteger }"
     |
-    size         := listOfNodes size.
-    index        := start.
-    end          := stop min:size.
-    level        := -1. "/ to force evaluation of #ifFalse in loop
-    soVDt        := 0.
-    yTop         := y0.
-    yCtr         := yTop - (fontHeight // 2).
-    dyLvl        := imageInset + imageWidth.
-    figWidthDiv2 := imageWidth // 2.
-    figWidthDiv2 odd ifTrue:[figWidthDiv2 := figWidthDiv2 + 1].
+    end      := stop min:(listOfNodes size).
+    yBot     := y0.
+    yCtr     := yBot - (fontHeight // 2).
+    widthLvl := imageInset + imageWidth.
+    insetTxt := imageWidth + textInset.
+    figDiv2  := imageWidth // 2.
+    xOfLvl1  := self xOfFigureLevel:1.
+
+    showDirectoryIndicator ifTrue:[
+        indicatorExt := openIndicator extent // 2.
+    ].
 
     showLines ifTrue:[
-        soVDt := (figWidthDiv2 + (self xOfFigureLevel:1)) - dyLvl - dyLvl.
         self setMaskOrigin:(self viewOrigin + (0 @ 1) \\ (lineMask extent)).
-        defLineColor := lineColor ? fgColor.
     ].
 
-    [index <= end] whileTrue:[
-        node := listOfNodes at:index.
-        yBot := yTop + fontHeight.
+    parent   := 4711.                           "/ to force a recompute
+    prevNode := 4711.                           "/ to force a recomputation of the level
+
+    start to:end do:[:anIndex|
+        node := listOfNodes at:anIndex.
+        yTop := yBot - 1.
+        yBot := yBot + fontHeight.
         yCtr := yCtr + fontHeight.
 
-        (lv := node level) == level ifFalse:[
-            xFig   := self xOfFigureLevel:lv.
-            xStr   := self xOfStringLevel:lv.
-            xCross := xFig - dyLvl + figWidthDiv2.
-            level  := lv.
-            soVLn  := lv * dyLvl + soVDt.
+        parent ~~ node parent ifTrue:[
+            parent := node parent.
+
+            prevNode == parent ifTrue:[
+                level := level + 1.
+                xIcon := xIcon + widthLvl.
+            ] ifFalse:[
+                level := node level.
+                xIcon := level - 1 * widthLvl + xOfLvl1.
+            ].
+            xText  := xIcon + insetTxt.
+            xCross := xIcon - widthLvl + figDiv2.
+
+            showIndicator := (     showDirectoryIndicator
+                              and:[(parent notNil or:[showDirectoryIndicatorForRoot])
+                              and:[(xCross + indicatorExt x > x0 and:[(xCross - indicatorExt x) < x1])]]
+                             ).
+            showIcon      := xIcon < x1 and:[xText > x0].
+            showText      := xText < x1.
+
+            showLines ifTrue:[
+                showVLines := xCross >= x0 and:[parent notNil].
+                showHLine  := (     xIcon > x0
+                                and:[(parent notNil
+                                 or:[showDirectoryIndicatorForRoot and:[showDirectoryIndicator]])]
+                              ).
+            ].
         ].
 
-        (isSelected := self isInSelection:index) ifTrue:[
+        (isSelected := self isInSelection:anIndex) ifTrue:[
             self paint:hilightFgColor on:hilightBgColor
         ].
         showLines ifTrue:[
             isSelected ifFalse:[
-                self paint:defLineColor on:bgColor
+                self paint:lineColor on:bgColor
             ].
             self mask:lineMask.
 
             xCross < x1 ifTrue:[
-                (    ((x := xFig + figWidthDiv2) between:x0 and:x1)
+                (    ((x := xIcon + figDiv2) between:x0 and:x1)
                  and:[node isCollapsable
                  and:[node children notEmpty]]
                 ) ifTrue:[
                     self displayLineFromX:x y:yCtr toX:x y:yBot
                 ].
 
-                "/ vertical line from previous to current form
-                (xCross >= x0 and:[level ~~ 1]) ifTrue:[
-                    prnt := node parent children.
-                    prnt isEmpty ifTrue:[ ^ self ]. "/ error occured
-                    lv := prnt last == node ifTrue:[yCtr] ifFalse:[yBot].
-                    self displayLineFromX:xCross y:yTop - 1 toX:xCross y:lv
-                ].
-
-                "/ horizontal line from previous to current form
-                (     xFig > x0
-                 and:[(level ~~ 1
-                  or:[showDirectoryIndicatorForRoot and:[showDirectoryIndicator]])]
-                ) ifTrue:[
-                    self displayLineFromX:xCross y:yCtr toX:xFig y:yCtr
+                showHLine ifTrue:[
+                    self displayLineFromX:xCross y:yCtr toX:x y:yCtr
                 ]
             ].
 
-        "/  draw all vertical lines to left side
-            (xCross >= x0 and:[(rnode := node parent) notNil]) ifTrue:[
-                x := soVLn.
-                y := yTop - 1.
+            showVLines ifTrue:[
+                y := parent basicLastChild == node ifTrue:[yCtr] ifFalse:[yBot].
+                self displayLineFromX:xCross y:yTop toX:xCross y:y.
 
-                [((prnt := rnode parent) notNil and:[(x := x - dyLvl) >= x0])] whileTrue:[
-                    (prnt children last ~~ rnode and:[x <= x1]) ifTrue:[
-                        self displayLineFromX:x y:y toX:x y:yBot
+                x  := xCross.
+                p2 := parent.
+
+                [((p1 := p2 parent) notNil and:[(x := x - widthLvl) >= x0])] whileTrue:[
+                    (p1 basicLastChild ~~ p2 and:[x <= x1]) ifTrue:[
+                        self displayLineFromX:x y:yTop toX:x y:yBot
                     ].
-                    rnode := prnt
+                    p2 := p1
                 ]
             ].
             self mask:nil.
         ].
-        isSelected ifFalse:[
-            self paint:fgColor on:bgColor
-        ].
 
-        "/ draw image
-        (image := self figureFor:node) notNil ifTrue:[
-            (xFig < x1 and:[xStr > x0]) ifTrue:[
-                self displayForm:image x:xFig y:(yCtr - (image height // 2))
-            ]
-        ].
-
-        "/ draw text label
-        xStr < x1 ifTrue:[
-            self drawLabelIndex:index atX:xStr y:yCtr .
+        (showIcon and:[(icon := self figureFor:node) notNil]) ifTrue:[
+            self displayForm:icon x:xIcon y:(yCtr - (icon height // 2))
         ].
-
-        "/ draw directory indicator
-
-        (showDirectoryIndicator and:[node showIndicator]) ifTrue:[
-            (level ~~ 1 or:[showDirectoryIndicatorForRoot]) ifTrue:[
-                image  := node isCollapsable ifTrue:[openIndicator] ifFalse:[closeIndicator].
-                extent := image extent // 2.
-                x := extent x.
-
-                (xCross + x > x0 and:[(x := xCross - x) < x1]) ifTrue:[
-                    self displayForm:image x:x y:(yCtr - extent y)
-                ]
-            ]
+        showText ifTrue:[
+            isSelected ifFalse:[ self paint:fgColor on:bgColor ].
+            self drawLabelIndex:anIndex atX:xText y:yCtr .
         ].
-        "/ setup next line
-        index := index + 1.
-        yTop  := yBot.
+        (showIndicator and:[node showIndicator]) ifTrue:[
+            icon := node isCollapsable ifTrue:[openIndicator] ifFalse:[closeIndicator].
+            self displayForm:icon x:(xCross - indicatorExt x) y:(yCtr - indicatorExt y)
+        ].
+        prevNode := node.
     ]
 
 !
@@ -728,8 +740,6 @@
      x   "{ Class: SmallInteger }" 
     |
 
-    aList size == 0 ifTrue:[ ^ self ].
-
     strikeOut ifTrue:[
         y := fontHeight // 2.
         self paint:bgColor.
@@ -746,7 +756,7 @@
             aList do:[:sY|
                 y := sY - spc. self displayLineFromX:x0 y:y toX:x1 y:y.
                 y := y  + dY.  self displayLineFromX:x0 y:y toX:x1 y:y.
-            ]
+            ].
         ]
     ] ifFalse:[
         hilightStyle == #motif ifTrue:[
@@ -814,7 +824,7 @@
 buttonPress:button x:x y:y
     "check for indicator
     "
-    |expand node lineNr isExpandable|
+    |expand node lineNr sensor what|
 
     lineNr := self indicatiorLineForButton:button atX:x y:y.
 
@@ -823,10 +833,6 @@
     ].
     node := listOfNodes at:lineNr.
 
-    node hasChildren ifFalse:[                  "/ no children exists
-        ^ super buttonPress:button x:x y:y
-    ].
-
     discardMotionEvents := true.
     dragIsActive  := false.
     clickPosition := nil.
@@ -838,40 +844,14 @@
             self selection:nil
         ]
     ].
-    isExpandable := node isExpandable.
-
-    self isCtrlMetaAltOrShiftPressed ifFalse:[
-        ^ self nodeAt:lineNr expand:isExpandable
-    ].
+    sensor := self sensor.
 
-    isExpandable ifTrue:[
-        supportsExpandAll ifFalse:[
-            ^ self nodeAt:lineNr expand:isExpandable
-        ].
-        node expandAll
+    (sensor notNil and:[(sensor ctrlDown or:[sensor shiftDown])]) ifTrue:[
+        what := nil
     ] ifFalse:[
-        (node hasExpandedChildren) ifTrue:[
-            node hasChildrenWithSubChildren ifFalse:[
-                ^ self nodeAt:lineNr expand:isExpandable
-            ].
-            node collapseAllChildren
-        ] ifFalse:[
-            supportsExpandAll ifFalse:[
-                ^ self nodeAt:lineNr expand:isExpandable
-            ].
-            node expandAllChildren
-        ]
+        what := node isExpandable
     ].
-
-    node children isEmpty ifTrue:[
-     "/ no children; redraw selected line (image might change)
-        self redrawLine:lineNr.
-    ] ifFalse:[
-     "/ with children; update list and redraw to end.
-        self recomputeListFromNodeAt:lineNr
-    ]
-
-
+    self nodeAt:lineNr expand:what
 !
 
 buttonRelease:button x:x y:y
@@ -905,7 +885,7 @@
 indicatiorLineForButton:aButton atX:x y:y
     "returns linenumber assigned to indicator at x/y or 0
     "
-    |nr x0 node|
+    |sensor nr x0 node|
 
     (     enabled
      and:[showDirectoryIndicator
@@ -925,7 +905,6 @@
         ]
     ].            
     ^ 0
-
 !
 
 isCtrlMetaAltOrShiftPressed
@@ -1055,7 +1034,6 @@
     self redrawSelFrameForYs:sel fromX:x toX:maxX.
 
     self clippingRectangle:savClip.
-
 ! !
 
 !SelectionInTreeView methodsFor:'initialization'!
@@ -1064,9 +1042,8 @@
     super create.
     lineMask := lineMask onDevice:device.
 
-    lineColor notNil ifTrue:[
-        lineColor := lineColor onDevice:device
-    ]
+    lineColor := lineColor isNil ifTrue:[fgColor]
+                                ifFalse:[lineColor onDevice:device].
 !
 
 destroy
@@ -1105,7 +1082,7 @@
     |img x y keysAndIcons|
 
     imageOpened isNil ifTrue:[
-        imageOpened := (self class imageOpened) onDevice:device
+        imageOpened := self imageOnDevice:(self class imageOpened)
     ].
 
     imageClosed isNil ifTrue:[
@@ -1125,7 +1102,7 @@
     (keysAndIcons := self fetchDefaultImages) notNil ifTrue:[
         keysAndIcons keysAndValuesDo:[:aKey :anIcon|
             (anIcon isImage and:[aKey notNil]) ifTrue:[
-                registeredImages at:aKey put:(self imageOnDevice:anIcon copy)
+                registeredImages at:aKey put:(self imageOnDevice:anIcon)
             ]
         ]
     ].
@@ -1172,6 +1149,7 @@
     imageInset := 0.    "/ set during indication enabled
     imageWidth := 8.    "/ default: will change during startup
     self model:nil.     "/ creates a default model.
+
 !
 
 realize
@@ -1223,8 +1201,12 @@
         fontHeight odd ifTrue:[
             fontHeight := fontHeight + 1
         ].
+        "/ round and not odd: because of line drawing
 
-        imageWidth := extent x.
+        imageWidth := (extent x) // 2.
+        imageWidth odd ifTrue:[imageWidth := imageWidth + 1].
+        imageWidth := imageWidth * 2.
+
         self recomputeDirectoryIndicator.
         self computeNumberOfLinesShown.
     ]
@@ -1243,30 +1225,11 @@
     "get list from model and return the new list.
      If listMessage is nil, try aspectMessage for backward compatibilty.
     "
-    |msg list
-     runs "{ Class: SmallInteger }"
-     idx  "{ Class: SmallInteger }"
-    |
-    widthOfWidestLine := nil.
-
-    (msg := listMsg ? aspectMsg) notNil ifTrue:[
-        listOfNodes := model perform:msg.
+    |msg|
 
-        (runs := listOfNodes size) ~~ 0 ifTrue:[
-            self refetchDeviceResources.
-            idx  := 1.
-            list := OrderedCollection new:runs.
-
-            runs timesRepeat:[
-                list add:(listOfNodes at:idx) name.
-                idx := idx + 1.
-            ].
-            ^ list
-        ]
-    ].
-    listOfNodes := #().
-  ^ #()
-
+    widthOfWidestLine := nil.
+    listOfNodes := (msg := listMsg ? aspectMsg) notNil ifTrue:[model perform:msg] ifFalse:[#()].
+  ^ listOfNodes
 !
 
 model:aModel
@@ -1363,52 +1326,45 @@
     "
     |list time|
 
-    list := aList.
+    list := (aList size == 0) ifTrue:[#()] ifFalse:[aList].
+    super list:list keepSelection:keepSelection.
+    self refetchDeviceResources.
 
-    list size == 0 ifTrue:[
-        listOfNodes := #()
-    ] ifFalse:[
-        (list first respondsTo:#hasChildren) ifTrue:[
-            listOfNodes := aList.
-            self refetchDeviceResources.
-            list := listOfNodes collect:[:aNode| aNode name ].
-        ]
-    ].
-    super list:list keepSelection:keepSelection
 !
 
 nodeAt:anIndex expand:doExpand
     "expand or collapse the node at an index, anIndex dependent on the boolean state
      of doExpand
     "
-    |node|
+    |node isExpandable|
 
     node := listOfNodes at:anIndex.
+    isExpandable := node isExpandable.
 
-    node hasChildren ifFalse:[          "/ no children exists
-        ^ self
-    ].
-    node isExpandable ifTrue:[
-        doExpand ifFalse:[^ self].      "/ already expanded
-        node expand
+    isExpandable == doExpand ifTrue:[
+        isExpandable ifTrue:[node expand]
+                    ifFalse:[node collapse]
     ] ifFalse:[
-        doExpand ifTrue:[^ self].       "/ already collapsed
-        node collapse
+        doExpand notNil ifTrue:[
+            ^ self
+        ].
+        node hasExpandedChildren ifTrue:[
+            node collapseAll.
+            node expand.
+        ] ifFalse:[
+            node expandAll
+        ]
     ].
 
     node children isEmpty ifTrue:[
-     "/ no children; redraw selected line (image might change)
-        self redrawLine:anIndex.
-    ] ifFalse:[
-     "/ with children; update list and redraw to end.
-        self recomputeListFromNodeAt:anIndex
-    ]
-
-
-!
-
-recomputeListFromNodeAt:anIndex
-
+        "/
+        "/ no children; redraw selected line (icon might change)
+        "/
+        ^ self redrawLine:anIndex
+    ].
+    "/
+    "/ list of nodes has changed; recompute list and redraw from index to end
+    "/
     model removeDependent:self.
     model recomputeList.
     model addDependent:self.
@@ -1434,7 +1390,7 @@
         node := listOfNodes at:nr.
         dObj := self dragObjectForNode:node.
         dObj theObject:(node contents).
-        dLbl := LabelAndIcon icon:(self figureFor:node) string:(list at:nr).
+        dLbl := LabelAndIcon icon:(self figureFor:node) string:(node name).
         dObj displayObject:dLbl.
         dObj
     ].
@@ -1443,7 +1399,8 @@
         converted := OrderedCollection new.
         collection keysAndValuesDo:[:nr :obj | 
             (dObj := dragObjectConverter value:obj) notNil ifTrue:[
-                dLbl := LabelAndIcon icon:(self figureFor:(listOfNodes at:nr)) string:(list at:nr).
+                node := listOfNodes at:nr.
+                dLbl := LabelAndIcon icon:(self figureFor:node) string:(node name).
                 converted displayObject:dLbl.
                 converted add:dObj
             ]
@@ -1481,78 +1438,77 @@
 lengthOfLongestLineBetween:firstLine and:lastLine
     "return the length (in characters) of the longest line in a line-range
     "
-    |max|
-
-    max := self widthOfContents:firstLine and:lastLine.
-  ^ (max // fontWidth) + 1
+    ^ self widthOfContents // fontWidth + 1
 !
 
 widthOfContents
     "return the width of the contents in pixels
      - used for scrollbar interface"
 
-    list isNil ifTrue:[^ 0].
+    listOfNodes isNil ifTrue:[^ 0].
 
     (widthOfWidestLine isNil or:[widthOfWidestLine == 0]) ifTrue:[
-        widthOfWidestLine := self widthOfContents:1 and:(self size).
+        widthOfWidestLine := self widthOfLongestLine
     ].
   ^ widthOfWidestLine + (leftMargin * 2)
 
 !
 
-widthOfContents:firstLine and:lastLine
-    "return the length (in pixels) of the longest line in a line-range
+widthOfLongestLine
+    "return the width of the longest line in pixels
     "
-    |parent name item tmpValue
-     max      "{ Class: SmallInteger }"
-     index    "{ Class: SmallInteger }"
-     runs     "{ Class: SmallInteger }"
+    |parent array pItem
+     startX   "{ Class: SmallInteger }"
+     deltaX   "{ Class: SmallInteger }"
      level    "{ Class: SmallInteger }"
-     xOfStr   "{ Class: SmallInteger }"
-     dltX     "{ Class: SmallInteger }"
      width    "{ Class: SmallInteger }"
-     newSz    "{ Class: SmallInteger }"
      maxSz    "{ Class: SmallInteger }"|
 
-    (    (listOfNodes size == 0)
-     or:[(runs := lastLine min:(listOfNodes size)) < firstLine]
-    ) ifTrue:[
-        ^ 0
-    ].
-
+    array  := Array new:30 withAll:0.
+    parent := nil.
+    maxSz  := 1.
     level  := 1.
-    xOfStr := self xOfStringLevel:level.
-    max    := xOfStr.
-    dltX   := imageInset + imageWidth.
-    width  := '1' widthOn:self.
-    parent := 4711.    "/ to force a computation
-    index  := firstLine.
-    runs   := runs - index + 1.
+
+    listOfNodes do:[:anItem|
+        anItem parent ~~ parent ifTrue:[
+            array at:level put:maxSz.
+
+            (parent := anItem parent) == pItem ifTrue:[level := level + 1]
+                                              ifFalse:[level := anItem level].
+            maxSz := array at:level.
+        ].
+        pItem := anItem.
+        maxSz := maxSz max:(anItem name size).
+    ].
+    array at:level put:maxSz.
 
-    runs timesRepeat:[
-        item  := listOfNodes at:index.
-        name  := item name.
-        index := index + 1.
+    startX := self xOfStringLevel:1.
+    deltaX := imageInset + imageWidth.
+    width  := '1' widthOn:self.
+    maxSz  := 0.
 
-        (newSz := name size) ~~ 0 ifTrue:[
-            item parent ~~ parent ifTrue:[
-                parent   := item parent.
-                tmpValue := item level.
-                xOfStr   := xOfStr + ((tmpValue - level) * dltX).
-                level    := tmpValue.
-                maxSz    := 0.
-            ].
-            maxSz < newSz ifTrue:[
-                maxSz := newSz.
-                max   := max max:(xOfStr + (maxSz * width)).
-            ]
-        ]
+    array do:[:el|
+        el == 0 ifTrue:[ ^ maxSz + leftOffset ].
+        maxSz  := maxSz max:(el * width + startX).
+        startX := startX + deltaX.
     ].
-    ^ max + leftOffset.
+! !
+
+!SelectionInTreeView methodsFor:'private redefinitions'!
+
+expandTabs
+    "nothing to do
+    "
 
 
 !
 
+list:aCollection expandTabs:expand scanForNonStrings:scan
+
+    includesNonStrings := false.
+    self list:aCollection expandTabs:false scanForNonStrings:false includesNonStrings:false
+!
+
 withoutRedrawAt:anIndex put:aString
     "change a line without redisplay"
 
@@ -1560,15 +1516,16 @@
 
     width := widthOfWidestLine.
     widthOfWidestLine := nil.
-
     super withoutRedrawAt:anIndex put:aString.
+    widthOfWidestLine := width.
 
-    (widthOfWidestLine := width) notNil ifTrue:[
-        width := self widthOfContents:anIndex and:anIndex.
+    (widthOfWidestLine notNil and:[aString size ~~ 0]) ifTrue:[
+        width := self xOfStringNode:(listOfNodes at:anIndex)
+               + (aString widthOn:self)
+               + leftOffset.
+
         widthOfWidestLine := widthOfWidestLine max:width.
     ].
-
-
 ! !
 
 !SelectionInTreeView methodsFor:'queries'!
@@ -1585,18 +1542,17 @@
             ^ img
         ].
         icon isImage ifTrue:[
-            img := self imageOnDevice:(icon copy).
+            img := self imageOnDevice:icon.
             registeredImages at:icon put:img.
           ^ img
         ]
     ].
 
-    "/ fallback solution
+    aNode hasChildren ifFalse:[
+        ^ imageItem
+    ].
+    ^ aNode hidden ifTrue:[imageClosed] ifFalse:[imageOpened]
 
-    aNode hasChildren ifTrue:[
-        ^ aNode isExpandable ifTrue:[imageClosed] ifFalse:[imageOpened]
-    ].
-  ^ imageItem
 !
 
 indexOfNode:aNode
@@ -1818,7 +1774,9 @@
     |index|
 
     (index := self selectedIndex) ~~ 0 ifTrue:[
-        self nodeAt:index expand:doExpand
+        (listOfNodes at:index) hasChildren ifTrue:[
+            self nodeAt:index expand:doExpand
+        ]
     ].
 
 !
@@ -1834,5 +1792,5 @@
 !SelectionInTreeView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/SelectionInTreeView.st,v 1.53 1998-04-04 08:45:17 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/SelectionInTreeView.st,v 1.54 1998-04-08 07:04:19 ca Exp $'
 ! !