SelectionInTreeView.st
changeset 848 29f1947578b8
parent 847 8395a2d05464
child 850 70c2c0e9318f
--- a/SelectionInTreeView.st	Wed Apr 08 11:48:56 1998 +0200
+++ b/SelectionInTreeView.st	Thu Apr 09 13:37:00 1998 +0200
@@ -17,7 +17,7 @@
 		lineColor computeResources showRoot showDirectoryIndicator
 		closeIndicator openIndicator showDirectoryIndicatorForRoot
 		imageOpened imageClosed imageItem discardMotionEvents
-		registeredImages supportsExpandAll'
+		registeredImages supportsExpandAll buildInArray'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Views-Text'
@@ -473,6 +473,27 @@
 
 !SelectionInTreeView methodsFor:'drawing'!
 
+drawFromVisibleLine:startVisLineNr to:endVisLineNr with:fg and:bg
+    "redraw a visible line range with clearing the background
+    "
+    |y0 y1 sz|
+
+    shown ifTrue:[
+        y0  := self yOfVisibleLine:startVisLineNr.
+        y0  := y0 - 1.
+        sz  := endVisLineNr - startVisLineNr + 1.
+        y1  := sz * fontHeight.
+
+    "/  clear rectangle line and set background color
+        self paint:bg.
+        self fillRectangleX:0 y:y0 width:width height:y1.
+
+        (y1 := self visibleLineToAbsoluteLine:startVisLineNr) notNil ifTrue:[
+            self redrawLinesX:0 y:y0 toX:width start:y1 stop:(y1 + sz)
+        ]
+    ]
+!
+
 drawLine:line atX:atX inVisible:visLineNr with:fg and:bg
     self drawFromVisibleLine:visLineNr to:visLineNr with:fg and:bg
 
@@ -510,39 +531,26 @@
           height:(endVisLineNr - startVisLineNr + 1 * fontHeight)
 
 
-! !
-
-!SelectionInTreeView methodsFor:'drawing basics'!
+!
 
-drawFromVisibleLine:startVisLineNr to:endVisLineNr with:fg and:bg
-    "redraw a visible line range with clearing the background
-    "
-    |y0 y1 sz|
+redrawIconAndIndicatorAt:aLnNr
+    |visLineNr x0 x1 lv|
 
     shown ifTrue:[
-        y0  := self yOfVisibleLine:startVisLineNr.
-        y0  := y0 - 1.
-        sz  := endVisLineNr - startVisLineNr + 1.
-        y1  := sz * fontHeight.
+        visLineNr := self listLineToVisibleLine:aLnNr.
+        visLineNr notNil ifTrue:[
+            lv := (listOfNodes at:aLnNr) level.
+            x1 := (imageWidth + (self xOfFigureLevel:lv)) min:width.
+            x0 := (self xOfFigureLevel:(lv - 1)) max:0.
 
-    "/  clear rectangle line and set background color
-        self paint:bg.
-        self fillRectangleX:0 y:y0 width:width height:y1.
-
-        (y1 := self visibleLineToAbsoluteLine:startVisLineNr) notNil ifTrue:[
-            self redrawLinesX:0 y:y0 toX:width start:y1 stop:(y1 + sz)
+            (x0 > width or:[x1 < 0]) ifFalse:[
+                self redrawX:x0
+                           y:(self yOfVisibleLine:visLineNr)
+                       width:(x1 - x0)
+                      height:fontHeight
+            ]
         ]
-    ]
-!
-
-drawLabelIndex:anIndex atX:x y:yCenter
-    "draw text label at x and y centered
-    "
-    |lbl|
-
-    (lbl := (listOfNodes at:anIndex) name) notNil ifTrue:[
-        self displayOpaqueString:lbl x:x y:(yCenter + labelOffsetY).
-    ]    
+    ].
 !
 
 redrawIndicatorLine:aLineNr
@@ -586,30 +594,153 @@
 
 
 
+! !
+
+!SelectionInTreeView methodsFor:'drawing basics'!
+
+drawLabelIndex:anIndex atX:x y:yCenter
+    "draw text label at x and y centered
+    "
+    |lbl y|
+
+    (lbl := (listOfNodes at:anIndex) name) notNil ifTrue:[
+        y := yCenter + labelOffsetY.
+        self displayOpaqueString:lbl x:x y:y.
+    ]    
+!
+
+drawVHLinesX:x0 y:y0 toX:x1 start:start stop:stop
+    "redraw from line to line without clearing the background
+    "
+    |node prevNode parent p1 p2 showVLines showHLine lv nxtPrnt
+
+     x        "{ Class:SmallInteger }"
+     y        "{ Class:SmallInteger }"
+
+     yTop     "{ Class:SmallInteger }"
+     yBot     "{ Class:SmallInteger }"
+     yCtr     "{ Class:SmallInteger }"
+
+     begHLnY  "{ Class:SmallInteger }"
+     begHLnX  "{ Class:SmallInteger }"
+     endHLnX  "{ Class:SmallInteger }"
+
+     widthLvl "{ Class:SmallInteger }"
+     offsHLnX "{ Class:SmallInteger }"
+
+     level    "{ Class:SmallInteger }"
+     minLevel "{ Class:SmallInteger }"
+     minVLnX  "{ Class:SmallInteger }"
+    |
+    yBot     := y0.
+    yCtr     := yBot - (fontHeight // 2).
+    widthLvl := imageInset + imageWidth.
+    offsHLnX := imageWidth // 2 + (self xOfFigureLevel:-1).
+
+    parent   := 4711.                           "/ to force a recompute
+    prevNode := 4711.                           "/ to force a recomputation of the level
+
+    self setMaskOrigin:(self viewOrigin + (0 @ 1) \\ (lineMask extent)).
+    self paint:lineColor on:bgColor.
+    self mask:lineMask.
+    begHLnY  := y0.
+    minLevel := self smallestLevelOfNodesBetween:start and:stop.
+    minVLnX  := self xOfFigureLevel:minLevel.
+
+    buildInArray atAllPut:0.
+
+    start == 1 ifTrue:[
+        begHLnY := yCtr + fontHeight.
+    ].
+
+    start to:stop do:[:anIndex|
+        node := listOfNodes at:anIndex.
+        yTop := yBot - 1.
+        yBot := yBot + fontHeight.
+        yCtr := yCtr + fontHeight.
+
+        (nxtPrnt := node parent) ~~ parent ifTrue:[
+            parent := nxtPrnt.
+
+            prevNode == parent ifTrue:[
+                level := level + 1.
+                begHLnX := endHLnX.
+            ] ifFalse:[
+                level   := node level.
+                begHLnX := node level * widthLvl + offsHLnX.
+            ].
+
+            endHLnX := begHLnX + widthLvl.
+            showVLines := begHLnX >= x0 and:[parent notNil].
+            showHLine  := (      x0 < endHLnX
+                            and:[x1 > begHLnX
+                            and:[(     parent notNil
+                                   or:[showDirectoryIndicatorForRoot
+                                  and:[showDirectoryIndicator]]
+                                 )
+                                ]]
+                          ).
+        ].
+
+        showHLine ifTrue:[
+            self displayLineFromX:begHLnX y:yCtr toX:endHLnX y:yCtr
+        ].
+
+        showVLines ifTrue:[
+            y  := (parent basicLastChild == node) ifTrue:[yCtr] ifFalse:[yBot].
+            x  := begHLnX.
+            p2 := parent.
+            lv := level - 1.
+            self displayLineFromX:x y:begHLnY toX:x y:y.
+
+            [((p1 := p2 parent) notNil and:[(x := x - widthLvl) >= x0])] whileTrue:[
+                (p1 basicLastChild ~~ p2 and:[x <= x1]) ifTrue:[
+                    x >= minVLnX ifTrue:[
+                        self displayLineFromX:x y:yTop toX:x y:yBot
+                    ] ifFalse:[
+                        buildInArray at:lv put:yBot
+                    ].
+                ].
+                lv := lv - 1.
+                p2 := p1
+            ]
+        ].
+        prevNode := node.
+        begHLnY  := yCtr.
+    ].
+
+    minLevel > 1 ifTrue:[
+        "/
+        "/ draw outstanding verical lines to left
+        "/
+        x := widthLvl + offsHLnX.
+        y := (start ~~ 1) ifTrue:[y0] ifFalse:[y0 + (fontHeight // 2)].
+
+        2 to:minLevel do:[:i|
+            x := x + widthLvl.
+
+            (yBot := buildInArray at:i) ~~ 0 ifTrue:[
+                self displayLineFromX:x y:y toX:x y:yBot
+            ].
+        ]
+    ].
+    self mask:nil.
+
 !
 
 redrawLinesX:x0 y:y0 toX:x1 start:start stop:stop
     "redraw from line to line without clearing the background
     "
-    |node prevNode parent icon isSelected p1 p2 indicatorExt
-
-     showIndicator
-     showVLines
-     showHLine
-     showIcon
-     showText
+    |node prevNode parent icon showIndc showIcon showText nxtPrnt
 
      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 }"
+     xIndc    "{ Class:SmallInteger }"
      xIcon    "{ Class:SmallInteger }"
      xText    "{ Class:SmallInteger }"
 
@@ -617,22 +748,29 @@
 
      widthLvl "{ Class:SmallInteger }"
      insetTxt "{ Class:SmallInteger }"
-     xOfLvl1  "{ Class:SmallInteger }"
+
+     offIndcX "{ Class:SmallInteger }"
+     offIndcY "{ Class:SmallInteger }"
+     offIconX "{ Class:SmallInteger }"
     |
-    end      := stop min:(listOfNodes size).
+    (end := stop min:(listOfNodes size)) < start ifTrue:[
+        ^ self
+    ].
     yBot     := y0.
     yCtr     := yBot - (fontHeight // 2).
     widthLvl := imageInset + imageWidth.
     insetTxt := imageWidth + textInset.
-    figDiv2  := imageWidth // 2.
-    xOfLvl1  := self xOfFigureLevel:1.
+    offIconX := self xOfFigureLevel:0.
+    showIndc := false.
 
     showDirectoryIndicator ifTrue:[
-        indicatorExt := openIndicator extent // 2.
+        icon     := openIndicator extent // 2.
+        offIndcX := imageWidth // 2 - widthLvl - icon x.
+        offIndcY := icon y.
     ].
 
     showLines ifTrue:[
-        self setMaskOrigin:(self viewOrigin + (0 @ 1) \\ (lineMask extent)).
+        self drawVHLinesX:x0 y:y0 toX:x1 start:start stop:end
     ].
 
     parent   := 4711.                           "/ to force a recompute
@@ -640,92 +778,45 @@
 
     start to:end do:[:anIndex|
         node := listOfNodes at:anIndex.
-        yTop := yBot - 1.
         yBot := yBot + fontHeight.
         yCtr := yCtr + fontHeight.
 
-        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]])]
-                              ).
-            ].
-        ].
+        (nxtPrnt := node parent) ~~ parent ifTrue:[
+            parent := nxtPrnt.
+            xIcon  := prevNode == parent ifTrue:[xIcon + widthLvl]
+                                        ifFalse:[node level * widthLvl + offIconX].
 
-        (isSelected := self isInSelection:anIndex) ifTrue:[
-            self paint:hilightFgColor on:hilightBgColor
-        ].
-        showLines ifTrue:[
-            isSelected ifFalse:[
-                self paint:lineColor on:bgColor
-            ].
-            self mask:lineMask.
-
-            xCross < x1 ifTrue:[
-                (    ((x := xIcon + figDiv2) between:x0 and:x1)
-                 and:[node isCollapsable
-                 and:[node children notEmpty]]
-                ) ifTrue:[
-                    self displayLineFromX:x y:yCtr toX:x y:yBot
-                ].
+            xText    := xIcon + insetTxt.
+            showIcon := xIcon < x1 and:[xText > x0].
+            showText := xText < x1.
 
-                showHLine ifTrue:[
-                    self displayLineFromX:xCross y:yCtr toX:x y:yCtr
-                ]
-            ].
-
-            showVLines ifTrue:[
-                y := parent basicLastChild == node ifTrue:[yCtr] ifFalse:[yBot].
-                self displayLineFromX:xCross y:yTop toX:xCross y:y.
+            showDirectoryIndicator ifTrue:[
+                xIndc := xIcon + offIndcX.
 
-                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
-                    ].
-                    p2 := p1
-                ]
-            ].
-            self mask:nil.
+                showIndc := (      (parent notNil or:[showDirectoryIndicatorForRoot])
+                              and:[(xIcon > x0 and:[xIndc < x1])]
+                            )
+            ]
         ].
 
         (showIcon and:[(icon := self figureFor:node) notNil]) ifTrue:[
             self displayForm:icon x:xIcon y:(yCtr - (icon height // 2))
         ].
+
         showText ifTrue:[
-            isSelected ifFalse:[ self paint:fgColor on:bgColor ].
+            (self isInSelection:anIndex) ifFalse:[
+                self paint:fgColor on:bgColor
+            ] ifTrue:[
+                self paint:hilightFgColor on:hilightBgColor
+            ].
             self drawLabelIndex:anIndex atX:xText y:yCtr .
         ].
-        (showIndicator and:[node showIndicator]) ifTrue:[
+        (showIndc and:[node showIndicator]) ifTrue:[
             icon := node isCollapsable ifTrue:[openIndicator] ifFalse:[closeIndicator].
-            self displayForm:icon x:(xCross - indicatorExt x) y:(yCtr - indicatorExt y)
+            self displayForm:icon x:xIndc y:(yCtr - offIndcY)
         ].
         prevNode := node.
     ]
-
 !
 
 redrawSelFrameForYs:aList fromX:x0 toX:x1
@@ -851,7 +942,8 @@
     ] ifFalse:[
         what := node isExpandable
     ].
-    self nodeAt:lineNr expand:what
+    self nodeAt:lineNr expand:what.
+
 !
 
 buttonRelease:button x:x y:y
@@ -1148,6 +1240,10 @@
     textInset  := 4.
     imageInset := 0.    "/ set during indication enabled
     imageWidth := 8.    "/ default: will change during startup
+
+    buildInArray := Array new:50.       "/ used for temporary calculation
+                                        "/ suppress garbage collection
+
     self model:nil.     "/ creates a default model.
 
 !
@@ -1264,27 +1360,47 @@
 selectionFromModel
     "set the selection derived from the selectionHolder
     "
-    |coll value sz|
+    |coll value sz upLst idx|
 
     (value := selectionHolder value) isNil ifTrue:[
         ^ self deselect
     ].
 
-    multipleSelectOk ifFalse:[
-        self selectNode:value
-    ] ifTrue:[
-        (sz := value size) ~~ 0 ifTrue:[
-            coll := OrderedCollection new:sz.
+    (multipleSelectOk and:[value isCollection]) ifFalse:[
+        ^ self selectNode:value
+    ].
+
+    (sz := value size) == 0 ifTrue:[
+        ^ self deselect
+    ].
+
+    sz == 1 ifTrue:[
+        ^ self selectNode:(value at:1)
+    ].
+
+    coll  := OrderedCollection new:sz.
+    upLst := false.
 
-            value do:[:aNode||i|
-                (i := self indexOfNode:aNode) notNil ifTrue:[
-                    coll add:i
-                ]
+    value do:[:aNode|
+        (idx := self indexOfNode:aNode) ~~ 0 ifTrue:[
+            coll add:idx
+        ] ifFalse:[
+            (self makeNodeVisible:aNode) notNil ifTrue:[
+                upLst := true
             ]
-        ].
-        coll size == 0 ifTrue:[self deselect]
-                      ifFalse:[self selection:coll]
-    ]
+        ]
+    ].
+
+    upLst ifTrue:[
+        coll clearContents.
+        selection := nil.
+        model recomputeList.
+
+        value do:[:aNode|
+            (idx := self indexOfNode:aNode) ~~ 0 ifTrue:[ coll add:idx ]
+        ]
+    ].
+    self selection:coll
 !
 
 selectionToModel
@@ -1333,14 +1449,37 @@
 
 !
 
+makeNodeVisible:aNode
+    "expand all nodes to make a node visible; the anchor from
+     where the list should be expanded is returned
+    "
+    |root prnt|
+
+    root := nil.
+
+    (prnt := aNode) notNil ifTrue:[
+        [ (prnt := prnt parent) notNil] whileTrue:[
+            prnt hidden ifTrue:[
+                root notNil ifTrue:[
+                    root expand
+                ].
+                root := prnt.
+                prnt expand.
+            ]
+        ]
+    ].
+    ^ root
+!
+
 nodeAt:anIndex expand:doExpand
     "expand or collapse the node at an index, anIndex dependent on the boolean state
      of doExpand
     "
-    |node isExpandable|
+    |node isExpandable oSz nSz wwl y0 y1 h cY rY mustRedraw nxtIdx|
 
     node := listOfNodes at:anIndex.
     isExpandable := node isExpandable.
+    mustRedraw   := false.
 
     isExpandable == doExpand ifTrue:[
         isExpandable ifTrue:[node expand]
@@ -1350,6 +1489,7 @@
             ^ self
         ].
         node hasExpandedChildren ifTrue:[
+            mustRedraw := (node children findFirst:[:c| c hidden ]) ~~ 0.
             node collapseAll.
             node expand.
         ] ifFalse:[
@@ -1361,18 +1501,61 @@
         "/
         "/ no children; redraw selected line (icon might change)
         "/
-        ^ self redrawLine:anIndex
+        ^ self redrawIconAndIndicatorAt:anIndex.
     ].
     "/
     "/ list of nodes has changed; recompute list and redraw from index to end
     "/
+    oSz := list size.
+    wwl := widthOfWidestLine.
     model removeDependent:self.
     model recomputeList.
     model addDependent:self.
+    list := self listFromModel.
 
-    list := self listFromModel.
-    self redrawFromLine:anIndex.
+    (nSz := list size) == oSz ifTrue:[
+        "/
+        "/ nothing changed; restore widthOfWidestLine
+        "/
+        widthOfWidestLine := wwl.
+        ^ self redrawIconAndIndicatorAt:anIndex
+    ].
+    shown ifFalse:[ ^ self ].
+    self redrawIconAndIndicatorAt:anIndex.
+
+    nxtIdx := anIndex + 1.
+
+    (mustRedraw or:[nxtIdx >= nSz]) ifTrue:[
+        ^ self redrawFromLine:nxtIdx
+    ].
+                
+    (wwl := self listLineToVisibleLine:nxtIdx) isNil ifTrue:[
+        ^ self
+    ].
+
+    h  := (nSz - oSz) abs * fontHeight.
+    y0 := self yOfVisibleLine:wwl.
+    y1 := y0 + h.
+    cY := height - y1 - 1.
+
+    cY < 40 ifTrue:[
+        self redrawFromLine:nxtIdx.
+    ] ifFalse:[
+        self catchExpose.
+
+        nSz > oSz ifTrue:[
+            self copyFrom:self x:0 y:y0 toX:0 y:y1 width:width height:cY async:true.
+        ] ifFalse:[
+            self copyFrom:self x:0 y:y1 toX:0 y:y0 width:width height:cY async:true.
+            y0 := y0 + cY.
+            h  := height - y0.
+        ].
+        self redrawX:0 y:y0 width:width height:h.
+        self waitForExpose.
+    ].
+    device flush.
     self contentsChanged.
+
 ! !
 
 !SelectionInTreeView methodsFor:'private - drag and drop'!
@@ -1442,6 +1625,51 @@
     ^ self widthOfContents // fontWidth + 1
 !
 
+smallestLevelOfNodesBetween:start and:stop
+    "returns the smallest level of the nodes in a line range
+    "
+    |prevNode currParent nextParent
+
+     lvl "{ Class:SmallInteger }"
+     min "{ Class:SmallInteger }"
+     end "{ Class:SmallInteger }"
+     beg "{ Class:SmallInteger }"
+    |
+
+    (end := stop min:(listOfNodes size)) < start ifTrue:[
+        ^ 0
+    ].
+
+    prevNode   := listOfNodes at:start.
+    currParent := prevNode parent.
+
+    currParent isNil ifTrue:[
+        ^ 1
+    ].
+
+    (min := prevNode level) == 2 ifTrue:[
+        ^ min
+    ].
+    beg := start + 1.
+
+    listOfNodes from:beg to:end do:[:currNode|
+        (nextParent := currNode parent) == currParent ifFalse:[
+            (currParent := nextParent) == prevNode ifFalse:[
+                (lvl := currNode level) == 2 ifTrue:[
+                    ^ 2
+                ].
+                min := min min:lvl
+            ]
+        ].
+        prevNode := currNode
+    ].
+    ^ min
+
+
+
+
+!
+
 widthOfContents
     "return the width of the contents in pixels
      - used for scrollbar interface"
@@ -1458,37 +1686,38 @@
 widthOfLongestLine
     "return the width of the longest line in pixels
     "
-    |parent array pItem
+    |parent pItem p
      startX   "{ Class: SmallInteger }"
      deltaX   "{ Class: SmallInteger }"
      level    "{ Class: SmallInteger }"
      width    "{ Class: SmallInteger }"
      maxSz    "{ Class: SmallInteger }"|
 
-    array  := Array new:30 withAll:0.
+    buildInArray atAllPut:0.
     parent := nil.
     maxSz  := 1.
     level  := 1.
 
     listOfNodes do:[:anItem|
-        anItem parent ~~ parent ifTrue:[
-            array at:level put:maxSz.
+        (p := anItem parent) ~~ parent ifTrue:[
+            buildInArray at:level put:maxSz.
 
-            (parent := anItem parent) == pItem ifTrue:[level := level + 1]
-                                              ifFalse:[level := anItem level].
-            maxSz := array at:level.
+            (parent := p) == pItem ifTrue:[level := level + 1]
+                                  ifFalse:[level := anItem level].
+
+            maxSz := buildInArray at:level.
         ].
         pItem := anItem.
         maxSz := maxSz max:(anItem name size).
     ].
-    array at:level put:maxSz.
+    buildInArray at:level put:maxSz.
 
     startX := self xOfStringLevel:1.
     deltaX := imageInset + imageWidth.
     width  := '1' widthOn:self.
     maxSz  := 0.
 
-    array do:[:el|
+    buildInArray do:[:el|
         el == 0 ifTrue:[ ^ maxSz + leftOffset ].
         maxSz  := maxSz max:(el * width + startX).
         startX := startX + deltaX.
@@ -1635,7 +1864,29 @@
 selectNode:aNode
     "change selection to a node
     "
-    self selection:(self indexOfNode:aNode)
+    |index parent|
+
+    aNode isNil ifTrue:[
+        index := nil
+    ] ifFalse:[
+        index := self indexOfNode:aNode.
+
+        index == 0 ifTrue:[
+            parent := self makeNodeVisible:aNode.
+            index  := self indexOfNode:parent.
+
+            index ~~ 0 ifTrue:[
+                selection := nil.
+                self model recomputeList.
+                "/ self nodeAt:index expand:true.
+                index := self indexOfNode:aNode
+            ].
+            index == 0 ifTrue:[
+                index := nil
+            ]
+        ]
+    ].
+    self selection:index 
 
 
 !
@@ -1793,5 +2044,5 @@
 !SelectionInTreeView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/SelectionInTreeView.st,v 1.55 1998-04-08 09:48:56 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/SelectionInTreeView.st,v 1.56 1998-04-09 11:37:00 ca Exp $'
 ! !