update
authorca
Wed, 25 Feb 1998 15:36:47 +0100
changeset 785 6114a6e125c5
parent 784 f521b359ec84
child 786 bf1885e29419
update
SelTreeV.st
SelectionInTreeView.st
--- a/SelTreeV.st	Tue Feb 24 19:48:50 1998 +0100
+++ b/SelTreeV.st	Wed Feb 25 15:36:47 1998 +0100
@@ -12,15 +12,15 @@
 
 
 SelectionInListView subclass:#SelectionInTreeView
-	instanceVariableNames:'validateDoubleClickBlock selectionHolder rootHolder imageWidth
-		showLines listOfNodes imageInset textInset labelOffsetY lineMask
-		lineColor openIndicator computeResources closeIndicator showRoot
-		extentOpenIndicator extentCloseIndicator showDirectoryIndicator
-		showDirectoryIndicatorForRoot indicatorExtentDiv2 imageOpened
-		imageClosed imageItem discardMotionEvents registeredImages'
-	classVariableNames:'ImageOpened ImageClosed ImageItem OpenIndicator CloseIndicator'
-	poolDictionaries:''
-	category:'Views-Text'
+        instanceVariableNames:'validateDoubleClickBlock selectionHolder rootHolder imageWidth
+                showLines listOfNodes imageInset textInset labelOffsetY lineMask
+                lineColor openIndicator computeResources closeIndicator showRoot
+                extentOpenIndicator extentCloseIndicator showDirectoryIndicator
+                showDirectoryIndicatorForRoot indicatorExtentDiv2 imageOpened
+                imageClosed imageItem discardMotionEvents registeredImages'
+        classVariableNames:'ImageOpened ImageClosed ImageItem OpenIndicator CloseIndicator'
+        poolDictionaries:''
+        category:'Views-Text'
 !
 
 !SelectionInTreeView class methodsFor:'documentation'!
@@ -226,7 +226,7 @@
 nodeAtIndex:anIndex
     "returns node at an index or nil
     "
-    (anIndex notNil and:[anIndex ~~ 0 and:[anIndex <= listOfNodes size]]) ifTrue:[
+    (anIndex notNil and:[anIndex between:1 and:listOfNodes size]) ifTrue:[
         ^ listOfNodes at:anIndex
     ].
   ^ nil
@@ -436,7 +436,9 @@
 
 update:something with:aParameter from:aModel
     "one of my models changed its value
-    "              
+    "
+    |idx|
+
     aModel == rootHolder ifTrue:[
         ^ self rootFromModel
     ].
@@ -448,14 +450,20 @@
         something == #list ifTrue:[  
             ^ self getListFromModel
         ]
-    ].
+    ] ifFalse:[
+        (aModel isKindOf:TreeItem) ifTrue:[
+            something == #value ifTrue:[  
+                idx := self indexOfNode:aModel.
 
-    (aModel isKindOf: TreeItem) ifTrue:[
-        something == #value ifTrue:[  
-            ^ self redrawLine: (self indexOfNode: aModel)
-        ].
-        something == #children ifTrue:[
-            ^ model recomputeList
+                idx ~~ 0 ifTrue:[
+                    list at:idx put:(aModel name).
+                    self redrawLine:idx
+                ].
+                ^ self
+            ].
+            something == #children ifTrue:[
+                ^ model recomputeList
+            ]
         ]
     ].
     ^ super update:something with:aParameter from:aModel.
@@ -533,32 +541,41 @@
 redrawLinesX:x0 y:y0 toX:x1 start:start stop:stop
     "redraw from line to line without clearing the background
     "
-    |chgdPaint node image isSelected
-     ext
-     x      "{ 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 }"
-     idx    "{ Class:SmallInteger }"
-     level
-     lv     "{ Class:SmallInteger }"
+    |node image isSelected defLineColor rnode ext 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 }"
     |
-    level := nil. "/ to force evaluation of #ifFalse in loop
-    yTop  := y0.
-    index := start.
-    size  := listOfNodes size.
-    end   := stop min:size.
-
+    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].
-    yCtr := yTop - (fontHeight // 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.
@@ -566,42 +583,34 @@
         yCtr := yCtr + fontHeight.
 
         (lv := node level) == level ifFalse:[
-            level  := lv.
             xFig   := self xOfFigureLevel:lv.
             xStr   := self xOfStringLevel:lv.
-            xCross := (self xOfFigureLevel:(lv-1)) + figWidthDiv2.
+            xCross := xFig - dyLvl + figWidthDiv2.
+            level  := lv.
+            soVLn  := lv * dyLvl + soVDt.
         ].
 
         (isSelected := self isInSelection:index) ifTrue:[
-            self paint:hilightFgColor on:hilightBgColor.
-        ] ifFalse:[
-            self paint:fgColor on:bgColor.
+            self paint:hilightFgColor on:hilightBgColor
         ].
-
         showLines ifTrue:[
-            chgdPaint := (lineColor isNil or:[isSelected]) not.
-
-            chgdPaint ifTrue:[
-                self paint:lineColor.
+            isSelected ifFalse:[
+                self paint:defLineColor on:bgColor
             ].
-
             self mask:lineMask.
-            self setMaskOrigin:(self viewOrigin + (0 @ 1) \\ (lineMask extent)).
 
             xCross < x1 ifTrue:[
                 (    ((x := xFig + figWidthDiv2) between:x0 and:x1)
                  and:[node isCollapsable
-                 and:[node numberOfChildren ~~ 0]]
+                 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
-                 and:["node parent children notEmpty and: ["node parent children last == node"]"]]
-                ) ifTrue:[
-                    self displayLineFromX:xCross y:yTop - 1 toX:xCross y:yCtr
+                (xCross >= x0 and:[level ~~ 1]) ifTrue:[
+                    lv := node parent children last == node ifTrue:[yCtr] ifFalse:[yBot].
+                    self displayLineFromX:xCross y:yTop - 1 toX:xCross y:lv
                 ].
 
                 "/ horizontal line from previous to current form
@@ -614,34 +623,26 @@
             ].
 
         "/  draw all vertical lines to left side
-            xCross >= x0 ifTrue:[
-                idx := index.
-
-                [(lv > 0 and:[(idx := idx + 1) <= size])] whileTrue:[
-                    (x := (listOfNodes at:idx) level) <= lv ifTrue:[
-                        lv := x - 1.
+            (xCross >= x0 and:[(rnode := node parent) notNil]) ifTrue:[
+                x := soVLn.
+                y := yTop - 1.
 
-                        (x  := (self xOfFigureLevel:lv) + figWidthDiv2) < x0 ifTrue:[
-                            lv := 0
-                        ] ifFalse:[
-                            x <= x1 ifTrue:[
-                                self displayLineFromX:x y:yTop - 1 toX:x y:yBot
-                            ]
-                        ]
-                    ]
+                [((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
+                    ].
+                    rnode := prnt
                 ]
             ].
             self mask:nil.
-
-            chgdPaint ifTrue:[
-                isSelected ifTrue:[self paint:hilightFgColor on:hilightBgColor]
-                          ifFalse:[self paint:fgColor        on:bgColor]
-            ]            
+        ].
+        isSelected ifFalse:[
+            self paint:fgColor on:bgColor
         ].
 
         "/ draw image
         (image := self figureFor:node) notNil ifTrue:[
-            (xFig < x1 and:[(xFig + image width) > x0]) ifTrue:[
+            (xFig < x1 and:[xStr > x0]) ifTrue:[
                 self displayForm:image x:xFig y:(yCtr - (image height // 2))
             ]
         ].
@@ -662,10 +663,10 @@
                     image := closeIndicator.
                     ext := extentCloseIndicator.
                 ].
-                idx := ext x.
+                x := ext x.
 
-                (xCross - idx < x1 and:[xCross + idx > x0]) ifTrue:[
-                    self displayForm:image x:(xCross - idx) y:(yCtr - ext y)
+                (xCross - x < x1 and:[xCross + x > x0]) ifTrue:[
+                    self displayForm:image x:(xCross - x) y:(yCtr - ext y)
                 ]
             ]
         ].
@@ -673,54 +674,6 @@
         index := index + 1.
         yTop  := yBot.
     ]
-!
-
-redrawX:x y:y width:w height:h
-    "a region must be redrawn"
-
-    |saveClip
-     y0       "{ Class:SmallInteger }"
-     y1       "{ Class:SmallInteger }"
-     visStart "{ Class:SmallInteger }"
-     visEnd   "{ Class:SmallInteger }"
-     startLn
-     stopLn   "{ Class:SmallInteger }"
-     maxY     "{ Class:SmallInteger }"
-     startY   "{ Class:SmallInteger }"|
-
-    shown ifFalse:[^ self].
-
-    visStart := self visibleLineOfY:(y + 1).
-    visEnd   := self visibleLineOfY:(y + h).
-    startLn  := self visibleLineToAbsoluteLine:visStart.
-
-    self paint:bgColor.
-    self fillRectangleX:x y:y width:w height:h.
-
-    startLn notNil ifTrue:[
-        startY := (self yOfVisibleLine:visStart) -1.
-        stopLn := startLn + visEnd - visStart.
-
-        saveClip := clipRect.
-        self clippingRectangle:(Rectangle left:x top:y width:w height:h).
-
-        self hasSelection ifTrue:[
-            maxY := y + h.
-
-            self selectionDo:[:i|
-                (i between:startLn and:stopLn) ifTrue:[
-                    self paint:hilightBgColor.
-                    y0 := (startY + (i - startLn * fontHeight)).
-                    y1 := (y0 + fontHeight) min:maxY.
-                    y0 := y0 max:y.
-                    self fillRectangleX:x y:y0 width:w height:y1 - y0
-                ]
-            ]
-        ].
-        self redrawLinesX:x y:startY toX:(x + w) start:startLn stop:stopLn.
-        self clippingRectangle:saveClip.
-    ].
-
 ! !
 
 !SelectionInTreeView methodsFor:'enumerating'!
@@ -835,15 +788,18 @@
 
             nr notNil ifTrue:[
                 node := listOfNodes at:nr.
-                x0   := self xOfFigureLevel:(node level - 1).
+                node hasChildren ifTrue:[
+                    x0   := self xOfFigureLevel:(node level - 1).
 
-                (x > x0 and:[(x0 + imageWidth) > x and:[node numberOfChildren ~~ 0]]) ifTrue:[
-                    ^ nr
+                    (x > x0 and:[(x0 + imageWidth) > x and:[node children notEmpty]]) ifTrue:[
+                        ^ nr
+                    ]
                 ]
             ]
         ]
     ].            
     ^ 0
+
 !
 
 key:key select:index x:x y:y
@@ -864,6 +820,53 @@
     ].
 
     self gotoLine:index
+!
+
+redrawX:x y:y width:w height:h
+    "a region must be redrawn"
+
+    |saveClip startLn
+     y0       "{ Class:SmallInteger }"
+     y1       "{ Class:SmallInteger }"
+     visStart "{ Class:SmallInteger }"
+     visEnd   "{ Class:SmallInteger }"
+     stopLn   "{ Class:SmallInteger }"
+     maxY     "{ Class:SmallInteger }"
+     startY   "{ Class:SmallInteger }"|
+
+    shown ifFalse:[^ self].
+
+    visStart := self visibleLineOfY:(y + 1).
+    startLn  := self visibleLineToAbsoluteLine:visStart.
+
+    self paint:bgColor.
+    self fillRectangleX:x y:y width:w height:h.
+
+    startLn notNil ifTrue:[
+        visEnd := self visibleLineOfY:(y + h).
+        startY := (self yOfVisibleLine:visStart) -1.
+        stopLn := startLn + visEnd - visStart.
+
+        saveClip := clipRect.
+        self clippingRectangle:(Rectangle left:x top:y width:w height:h).
+
+        self hasSelection ifTrue:[
+            maxY := y + h.
+
+            self selectionDo:[:i|
+                (i between:startLn and:stopLn) ifTrue:[
+                    self paint:hilightBgColor.
+                    y0 := (startY + (i - startLn * fontHeight)).
+                    y1 := (y0 + fontHeight) min:maxY.
+                    y0 := y0 max:y.
+                    self fillRectangleX:x y:y0 width:w height:y1 - y0
+                ]
+            ]
+        ].
+        self redrawLinesX:x y:startY toX:(x + w) start:startLn stop:stopLn.
+        self clippingRectangle:saveClip.
+    ].
+
 ! !
 
 !SelectionInTreeView methodsFor:'initialization'!
@@ -891,6 +894,13 @@
 
 !
 
+fetchDefaultImages
+    "returns a directory with default keys and images; could be
+     redefined by subclass.
+    "
+    ^ nil
+!
+
 fetchDeviceResources
     "initialize heavily used device resources - to avoid rendering
      images again and again later"
@@ -904,7 +914,7 @@
      images again and again later; returns maximum extent of the images used.
      Could be redefined by subclass
     "
-    |icon extent|
+    |img x y keysAndIcons|
 
     imageOpened isNil ifTrue:[
         imageOpened := (self class imageOpened) onDevice:device
@@ -913,16 +923,34 @@
     imageClosed isNil ifTrue:[
         imageClosed := self imageOnDevice:(self class imageClosed)
     ].
-    extent := (imageOpened extent) max:(imageClosed extent).
+
+    x := (imageOpened width)  max:(imageClosed width).
+    y := (imageOpened height) max:(imageClosed height).
 
     imageItem isNil ifTrue:[
         imageItem := self imageOnDevice:(self class imageItem)
     ].
 
-    (listOfNodes size > 0 and: [(icon := listOfNodes first icon) isImage]) ifTrue: [^icon extent].
+    x := (imageItem width)  max:x.
+    y := (imageItem height) max:y.
 
-    ^ extent max:(imageItem extent)
+    (keysAndIcons := self fetchDefaultImages) notNil ifTrue:[
+        keysAndIcons keysAndValuesDo:[:aKey :anIcon|
+            (anIcon isImage and:[aKey notNil]) ifTrue:[
+                registeredImages at:aKey put:(self imageOnDevice:anIcon copy)
+            ]
+        ]
+    ].
+    registeredImages keysAndValuesDo:[:k :img|
+        x := (img width)  max:x.
+        y := (img height) max:y.
+    ].
 
+    (listOfNodes size > 0 and:[(img := listOfNodes first icon) isImage]) ifTrue:[
+        x := (img width)  max:x.
+        y := (img height) max:y.
+    ].
+    ^ x @ y
 !
 
 getFontParameters
@@ -960,7 +988,6 @@
 realize
     super realize.
     self  refetchDeviceResources.
-
 !
 
 refetchDeviceResources
@@ -1086,7 +1113,7 @@
                 selectionHolder value:newSel.
             ] ifFalse:[
                 newSel do:[:aNode|
-                    (oldSel includes:aNode) ifFalse:[
+                    (oldSel includesIdentical:aNode) ifFalse:[
                         ^ selectionHolder value:newSel
                     ]
                 ]
@@ -1134,7 +1161,7 @@
             node collapse
         ].
 
-        node numberOfChildren == 0 ifTrue:[
+        node children isEmpty ifTrue:[
             "/ no children; redraw selected line (image might change)
             self redrawLine:anIndex.
         ] ifFalse:[
@@ -1267,23 +1294,25 @@
 figureFor:aNode
     "access figure for a node
     "
-    |unregisteredImage registeredImage|
+    |icon img|
+
+    (icon := aNode icon) notNil ifTrue:[
+        img := registeredImages at:icon ifAbsent:nil.
 
-    (unregisteredImage := aNode icon) notNil
-    ifTrue:
-    [       
-        (registeredImage := registeredImages at: unregisteredImage ifAbsent: nil) isNil
-        ifTrue:
-        [           
-            registeredImage := self imageOnDevice: unregisteredImage copy. 
-            registeredImages at: unregisteredImage put: registeredImage
+        img notNil ifTrue:[
+            ^ img
         ].
-        ^registeredImage
+        icon isImage ifTrue:[
+            img := self imageOnDevice:(icon copy).
+            registeredImages at:icon put:img.
+          ^ img
+        ]
     ].
 
+    "/ fallback solution
+
     aNode hasChildren ifTrue:[
-        aNode isExpandable ifTrue:[ ^ imageClosed ]
-                          ifFalse:[ ^ imageOpened ]
+        ^ aNode isExpandable ifTrue:[imageClosed] ifFalse:[imageOpened]
     ].
   ^ imageItem
 !
@@ -1291,16 +1320,15 @@
 indexOfNode:aNode
     "returns index of a node
     "
-    ^ listOfNodes findFirst:[:n| n == aNode ]
+    ^ listOfNodes identityIndexOf:aNode
 !
 
 xOfFigureLevel:aLevel
     "origin x where to draw the icon
     "
-    |l|
+    |l "{ Class:SmallInteger }"|
 
-    showRoot ifTrue:[l := aLevel]
-            ifFalse:[l := aLevel - 1].
+    l := showRoot ifTrue:[aLevel] ifFalse:[aLevel - 1].
 
     showDirectoryIndicator ifFalse:[
         l := l - 1
@@ -1338,36 +1366,28 @@
 selectFromListOfNames:aListOfNames
     "set selection from a list of names
     "
-    |node rdwNd|
+    |node rdwNd chgd|
 
     aListOfNames size < 1 ifTrue:[
         ^ self selection:nil
     ].
 
     node := model root.
+    chgd := false.
 
     aListOfNames do:[:el||next|
         next := node detectChild:[:e|e name = el].
 
         next notNil ifTrue:[
             node hidden ifTrue:[
-                rdwNd isNil ifTrue:[
-                    rdwNd := node.
-                    self selectNode:node.
-                ].
+                chgd := true.
                 node expand
             ].
             node := next
         ]
     ].
-
-    rdwNd notNil ifTrue:[
-        model removeDependent:self.
+    chgd ifTrue:[
         model recomputeList.
-        model addDependent:self.
-        list := self listFromModel.
-        self redrawFromLine:(self indexOfNode:rdwNd).
-        self contentsChanged.
     ].
     self selectNode:node.
 
@@ -1527,7 +1547,7 @@
                 node collapse
             ].
 
-            node numberOfChildren == 0 ifTrue:[
+            node children isEmpty ifTrue:[
                 "/ no children; redraw selected line (image might change)
                 self redrawLine:index.
             ] ifFalse:[
@@ -1541,6 +1561,7 @@
             ]
         ]
     ].
+
 !
 
 selectedNodesRemove
@@ -1554,5 +1575,5 @@
 !SelectionInTreeView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/Attic/SelTreeV.st,v 1.47 1998-02-24 15:42:16 tz Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/Attic/SelTreeV.st,v 1.48 1998-02-25 14:36:47 ca Exp $'
 ! !
--- a/SelectionInTreeView.st	Tue Feb 24 19:48:50 1998 +0100
+++ b/SelectionInTreeView.st	Wed Feb 25 15:36:47 1998 +0100
@@ -12,15 +12,15 @@
 
 
 SelectionInListView subclass:#SelectionInTreeView
-	instanceVariableNames:'validateDoubleClickBlock selectionHolder rootHolder imageWidth
-		showLines listOfNodes imageInset textInset labelOffsetY lineMask
-		lineColor openIndicator computeResources closeIndicator showRoot
-		extentOpenIndicator extentCloseIndicator showDirectoryIndicator
-		showDirectoryIndicatorForRoot indicatorExtentDiv2 imageOpened
-		imageClosed imageItem discardMotionEvents registeredImages'
-	classVariableNames:'ImageOpened ImageClosed ImageItem OpenIndicator CloseIndicator'
-	poolDictionaries:''
-	category:'Views-Text'
+        instanceVariableNames:'validateDoubleClickBlock selectionHolder rootHolder imageWidth
+                showLines listOfNodes imageInset textInset labelOffsetY lineMask
+                lineColor openIndicator computeResources closeIndicator showRoot
+                extentOpenIndicator extentCloseIndicator showDirectoryIndicator
+                showDirectoryIndicatorForRoot indicatorExtentDiv2 imageOpened
+                imageClosed imageItem discardMotionEvents registeredImages'
+        classVariableNames:'ImageOpened ImageClosed ImageItem OpenIndicator CloseIndicator'
+        poolDictionaries:''
+        category:'Views-Text'
 !
 
 !SelectionInTreeView class methodsFor:'documentation'!
@@ -226,7 +226,7 @@
 nodeAtIndex:anIndex
     "returns node at an index or nil
     "
-    (anIndex notNil and:[anIndex ~~ 0 and:[anIndex <= listOfNodes size]]) ifTrue:[
+    (anIndex notNil and:[anIndex between:1 and:listOfNodes size]) ifTrue:[
         ^ listOfNodes at:anIndex
     ].
   ^ nil
@@ -436,7 +436,9 @@
 
 update:something with:aParameter from:aModel
     "one of my models changed its value
-    "              
+    "
+    |idx|
+
     aModel == rootHolder ifTrue:[
         ^ self rootFromModel
     ].
@@ -448,14 +450,20 @@
         something == #list ifTrue:[  
             ^ self getListFromModel
         ]
-    ].
+    ] ifFalse:[
+        (aModel isKindOf:TreeItem) ifTrue:[
+            something == #value ifTrue:[  
+                idx := self indexOfNode:aModel.
 
-    (aModel isKindOf: TreeItem) ifTrue:[
-        something == #value ifTrue:[  
-            ^ self redrawLine: (self indexOfNode: aModel)
-        ].
-        something == #children ifTrue:[
-            ^ model recomputeList
+                idx ~~ 0 ifTrue:[
+                    list at:idx put:(aModel name).
+                    self redrawLine:idx
+                ].
+                ^ self
+            ].
+            something == #children ifTrue:[
+                ^ model recomputeList
+            ]
         ]
     ].
     ^ super update:something with:aParameter from:aModel.
@@ -533,32 +541,41 @@
 redrawLinesX:x0 y:y0 toX:x1 start:start stop:stop
     "redraw from line to line without clearing the background
     "
-    |chgdPaint node image isSelected
-     ext
-     x      "{ 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 }"
-     idx    "{ Class:SmallInteger }"
-     level
-     lv     "{ Class:SmallInteger }"
+    |node image isSelected defLineColor rnode ext 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 }"
     |
-    level := nil. "/ to force evaluation of #ifFalse in loop
-    yTop  := y0.
-    index := start.
-    size  := listOfNodes size.
-    end   := stop min:size.
-
+    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].
-    yCtr := yTop - (fontHeight // 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.
@@ -566,42 +583,34 @@
         yCtr := yCtr + fontHeight.
 
         (lv := node level) == level ifFalse:[
-            level  := lv.
             xFig   := self xOfFigureLevel:lv.
             xStr   := self xOfStringLevel:lv.
-            xCross := (self xOfFigureLevel:(lv-1)) + figWidthDiv2.
+            xCross := xFig - dyLvl + figWidthDiv2.
+            level  := lv.
+            soVLn  := lv * dyLvl + soVDt.
         ].
 
         (isSelected := self isInSelection:index) ifTrue:[
-            self paint:hilightFgColor on:hilightBgColor.
-        ] ifFalse:[
-            self paint:fgColor on:bgColor.
+            self paint:hilightFgColor on:hilightBgColor
         ].
-
         showLines ifTrue:[
-            chgdPaint := (lineColor isNil or:[isSelected]) not.
-
-            chgdPaint ifTrue:[
-                self paint:lineColor.
+            isSelected ifFalse:[
+                self paint:defLineColor on:bgColor
             ].
-
             self mask:lineMask.
-            self setMaskOrigin:(self viewOrigin + (0 @ 1) \\ (lineMask extent)).
 
             xCross < x1 ifTrue:[
                 (    ((x := xFig + figWidthDiv2) between:x0 and:x1)
                  and:[node isCollapsable
-                 and:[node numberOfChildren ~~ 0]]
+                 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
-                 and:["node parent children notEmpty and: ["node parent children last == node"]"]]
-                ) ifTrue:[
-                    self displayLineFromX:xCross y:yTop - 1 toX:xCross y:yCtr
+                (xCross >= x0 and:[level ~~ 1]) ifTrue:[
+                    lv := node parent children last == node ifTrue:[yCtr] ifFalse:[yBot].
+                    self displayLineFromX:xCross y:yTop - 1 toX:xCross y:lv
                 ].
 
                 "/ horizontal line from previous to current form
@@ -614,34 +623,26 @@
             ].
 
         "/  draw all vertical lines to left side
-            xCross >= x0 ifTrue:[
-                idx := index.
-
-                [(lv > 0 and:[(idx := idx + 1) <= size])] whileTrue:[
-                    (x := (listOfNodes at:idx) level) <= lv ifTrue:[
-                        lv := x - 1.
+            (xCross >= x0 and:[(rnode := node parent) notNil]) ifTrue:[
+                x := soVLn.
+                y := yTop - 1.
 
-                        (x  := (self xOfFigureLevel:lv) + figWidthDiv2) < x0 ifTrue:[
-                            lv := 0
-                        ] ifFalse:[
-                            x <= x1 ifTrue:[
-                                self displayLineFromX:x y:yTop - 1 toX:x y:yBot
-                            ]
-                        ]
-                    ]
+                [((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
+                    ].
+                    rnode := prnt
                 ]
             ].
             self mask:nil.
-
-            chgdPaint ifTrue:[
-                isSelected ifTrue:[self paint:hilightFgColor on:hilightBgColor]
-                          ifFalse:[self paint:fgColor        on:bgColor]
-            ]            
+        ].
+        isSelected ifFalse:[
+            self paint:fgColor on:bgColor
         ].
 
         "/ draw image
         (image := self figureFor:node) notNil ifTrue:[
-            (xFig < x1 and:[(xFig + image width) > x0]) ifTrue:[
+            (xFig < x1 and:[xStr > x0]) ifTrue:[
                 self displayForm:image x:xFig y:(yCtr - (image height // 2))
             ]
         ].
@@ -662,10 +663,10 @@
                     image := closeIndicator.
                     ext := extentCloseIndicator.
                 ].
-                idx := ext x.
+                x := ext x.
 
-                (xCross - idx < x1 and:[xCross + idx > x0]) ifTrue:[
-                    self displayForm:image x:(xCross - idx) y:(yCtr - ext y)
+                (xCross - x < x1 and:[xCross + x > x0]) ifTrue:[
+                    self displayForm:image x:(xCross - x) y:(yCtr - ext y)
                 ]
             ]
         ].
@@ -673,54 +674,6 @@
         index := index + 1.
         yTop  := yBot.
     ]
-!
-
-redrawX:x y:y width:w height:h
-    "a region must be redrawn"
-
-    |saveClip
-     y0       "{ Class:SmallInteger }"
-     y1       "{ Class:SmallInteger }"
-     visStart "{ Class:SmallInteger }"
-     visEnd   "{ Class:SmallInteger }"
-     startLn
-     stopLn   "{ Class:SmallInteger }"
-     maxY     "{ Class:SmallInteger }"
-     startY   "{ Class:SmallInteger }"|
-
-    shown ifFalse:[^ self].
-
-    visStart := self visibleLineOfY:(y + 1).
-    visEnd   := self visibleLineOfY:(y + h).
-    startLn  := self visibleLineToAbsoluteLine:visStart.
-
-    self paint:bgColor.
-    self fillRectangleX:x y:y width:w height:h.
-
-    startLn notNil ifTrue:[
-        startY := (self yOfVisibleLine:visStart) -1.
-        stopLn := startLn + visEnd - visStart.
-
-        saveClip := clipRect.
-        self clippingRectangle:(Rectangle left:x top:y width:w height:h).
-
-        self hasSelection ifTrue:[
-            maxY := y + h.
-
-            self selectionDo:[:i|
-                (i between:startLn and:stopLn) ifTrue:[
-                    self paint:hilightBgColor.
-                    y0 := (startY + (i - startLn * fontHeight)).
-                    y1 := (y0 + fontHeight) min:maxY.
-                    y0 := y0 max:y.
-                    self fillRectangleX:x y:y0 width:w height:y1 - y0
-                ]
-            ]
-        ].
-        self redrawLinesX:x y:startY toX:(x + w) start:startLn stop:stopLn.
-        self clippingRectangle:saveClip.
-    ].
-
 ! !
 
 !SelectionInTreeView methodsFor:'enumerating'!
@@ -835,15 +788,18 @@
 
             nr notNil ifTrue:[
                 node := listOfNodes at:nr.
-                x0   := self xOfFigureLevel:(node level - 1).
+                node hasChildren ifTrue:[
+                    x0   := self xOfFigureLevel:(node level - 1).
 
-                (x > x0 and:[(x0 + imageWidth) > x and:[node numberOfChildren ~~ 0]]) ifTrue:[
-                    ^ nr
+                    (x > x0 and:[(x0 + imageWidth) > x and:[node children notEmpty]]) ifTrue:[
+                        ^ nr
+                    ]
                 ]
             ]
         ]
     ].            
     ^ 0
+
 !
 
 key:key select:index x:x y:y
@@ -864,6 +820,53 @@
     ].
 
     self gotoLine:index
+!
+
+redrawX:x y:y width:w height:h
+    "a region must be redrawn"
+
+    |saveClip startLn
+     y0       "{ Class:SmallInteger }"
+     y1       "{ Class:SmallInteger }"
+     visStart "{ Class:SmallInteger }"
+     visEnd   "{ Class:SmallInteger }"
+     stopLn   "{ Class:SmallInteger }"
+     maxY     "{ Class:SmallInteger }"
+     startY   "{ Class:SmallInteger }"|
+
+    shown ifFalse:[^ self].
+
+    visStart := self visibleLineOfY:(y + 1).
+    startLn  := self visibleLineToAbsoluteLine:visStart.
+
+    self paint:bgColor.
+    self fillRectangleX:x y:y width:w height:h.
+
+    startLn notNil ifTrue:[
+        visEnd := self visibleLineOfY:(y + h).
+        startY := (self yOfVisibleLine:visStart) -1.
+        stopLn := startLn + visEnd - visStart.
+
+        saveClip := clipRect.
+        self clippingRectangle:(Rectangle left:x top:y width:w height:h).
+
+        self hasSelection ifTrue:[
+            maxY := y + h.
+
+            self selectionDo:[:i|
+                (i between:startLn and:stopLn) ifTrue:[
+                    self paint:hilightBgColor.
+                    y0 := (startY + (i - startLn * fontHeight)).
+                    y1 := (y0 + fontHeight) min:maxY.
+                    y0 := y0 max:y.
+                    self fillRectangleX:x y:y0 width:w height:y1 - y0
+                ]
+            ]
+        ].
+        self redrawLinesX:x y:startY toX:(x + w) start:startLn stop:stopLn.
+        self clippingRectangle:saveClip.
+    ].
+
 ! !
 
 !SelectionInTreeView methodsFor:'initialization'!
@@ -891,6 +894,13 @@
 
 !
 
+fetchDefaultImages
+    "returns a directory with default keys and images; could be
+     redefined by subclass.
+    "
+    ^ nil
+!
+
 fetchDeviceResources
     "initialize heavily used device resources - to avoid rendering
      images again and again later"
@@ -904,7 +914,7 @@
      images again and again later; returns maximum extent of the images used.
      Could be redefined by subclass
     "
-    |icon extent|
+    |img x y keysAndIcons|
 
     imageOpened isNil ifTrue:[
         imageOpened := (self class imageOpened) onDevice:device
@@ -913,16 +923,34 @@
     imageClosed isNil ifTrue:[
         imageClosed := self imageOnDevice:(self class imageClosed)
     ].
-    extent := (imageOpened extent) max:(imageClosed extent).
+
+    x := (imageOpened width)  max:(imageClosed width).
+    y := (imageOpened height) max:(imageClosed height).
 
     imageItem isNil ifTrue:[
         imageItem := self imageOnDevice:(self class imageItem)
     ].
 
-    (listOfNodes size > 0 and: [(icon := listOfNodes first icon) isImage]) ifTrue: [^icon extent].
+    x := (imageItem width)  max:x.
+    y := (imageItem height) max:y.
 
-    ^ extent max:(imageItem extent)
+    (keysAndIcons := self fetchDefaultImages) notNil ifTrue:[
+        keysAndIcons keysAndValuesDo:[:aKey :anIcon|
+            (anIcon isImage and:[aKey notNil]) ifTrue:[
+                registeredImages at:aKey put:(self imageOnDevice:anIcon copy)
+            ]
+        ]
+    ].
+    registeredImages keysAndValuesDo:[:k :img|
+        x := (img width)  max:x.
+        y := (img height) max:y.
+    ].
 
+    (listOfNodes size > 0 and:[(img := listOfNodes first icon) isImage]) ifTrue:[
+        x := (img width)  max:x.
+        y := (img height) max:y.
+    ].
+    ^ x @ y
 !
 
 getFontParameters
@@ -960,7 +988,6 @@
 realize
     super realize.
     self  refetchDeviceResources.
-
 !
 
 refetchDeviceResources
@@ -1086,7 +1113,7 @@
                 selectionHolder value:newSel.
             ] ifFalse:[
                 newSel do:[:aNode|
-                    (oldSel includes:aNode) ifFalse:[
+                    (oldSel includesIdentical:aNode) ifFalse:[
                         ^ selectionHolder value:newSel
                     ]
                 ]
@@ -1134,7 +1161,7 @@
             node collapse
         ].
 
-        node numberOfChildren == 0 ifTrue:[
+        node children isEmpty ifTrue:[
             "/ no children; redraw selected line (image might change)
             self redrawLine:anIndex.
         ] ifFalse:[
@@ -1267,23 +1294,25 @@
 figureFor:aNode
     "access figure for a node
     "
-    |unregisteredImage registeredImage|
+    |icon img|
+
+    (icon := aNode icon) notNil ifTrue:[
+        img := registeredImages at:icon ifAbsent:nil.
 
-    (unregisteredImage := aNode icon) notNil
-    ifTrue:
-    [       
-        (registeredImage := registeredImages at: unregisteredImage ifAbsent: nil) isNil
-        ifTrue:
-        [           
-            registeredImage := self imageOnDevice: unregisteredImage copy. 
-            registeredImages at: unregisteredImage put: registeredImage
+        img notNil ifTrue:[
+            ^ img
         ].
-        ^registeredImage
+        icon isImage ifTrue:[
+            img := self imageOnDevice:(icon copy).
+            registeredImages at:icon put:img.
+          ^ img
+        ]
     ].
 
+    "/ fallback solution
+
     aNode hasChildren ifTrue:[
-        aNode isExpandable ifTrue:[ ^ imageClosed ]
-                          ifFalse:[ ^ imageOpened ]
+        ^ aNode isExpandable ifTrue:[imageClosed] ifFalse:[imageOpened]
     ].
   ^ imageItem
 !
@@ -1291,16 +1320,15 @@
 indexOfNode:aNode
     "returns index of a node
     "
-    ^ listOfNodes findFirst:[:n| n == aNode ]
+    ^ listOfNodes identityIndexOf:aNode
 !
 
 xOfFigureLevel:aLevel
     "origin x where to draw the icon
     "
-    |l|
+    |l "{ Class:SmallInteger }"|
 
-    showRoot ifTrue:[l := aLevel]
-            ifFalse:[l := aLevel - 1].
+    l := showRoot ifTrue:[aLevel] ifFalse:[aLevel - 1].
 
     showDirectoryIndicator ifFalse:[
         l := l - 1
@@ -1338,36 +1366,28 @@
 selectFromListOfNames:aListOfNames
     "set selection from a list of names
     "
-    |node rdwNd|
+    |node rdwNd chgd|
 
     aListOfNames size < 1 ifTrue:[
         ^ self selection:nil
     ].
 
     node := model root.
+    chgd := false.
 
     aListOfNames do:[:el||next|
         next := node detectChild:[:e|e name = el].
 
         next notNil ifTrue:[
             node hidden ifTrue:[
-                rdwNd isNil ifTrue:[
-                    rdwNd := node.
-                    self selectNode:node.
-                ].
+                chgd := true.
                 node expand
             ].
             node := next
         ]
     ].
-
-    rdwNd notNil ifTrue:[
-        model removeDependent:self.
+    chgd ifTrue:[
         model recomputeList.
-        model addDependent:self.
-        list := self listFromModel.
-        self redrawFromLine:(self indexOfNode:rdwNd).
-        self contentsChanged.
     ].
     self selectNode:node.
 
@@ -1527,7 +1547,7 @@
                 node collapse
             ].
 
-            node numberOfChildren == 0 ifTrue:[
+            node children isEmpty ifTrue:[
                 "/ no children; redraw selected line (image might change)
                 self redrawLine:index.
             ] ifFalse:[
@@ -1541,6 +1561,7 @@
             ]
         ]
     ].
+
 !
 
 selectedNodesRemove
@@ -1554,5 +1575,5 @@
 !SelectionInTreeView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/SelectionInTreeView.st,v 1.47 1998-02-24 15:42:16 tz Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/SelectionInTreeView.st,v 1.48 1998-02-25 14:36:47 ca Exp $'
 ! !