SelectionInTreeView.st
changeset 490 1129f3cf5cea
parent 485 26e87be7210f
child 494 76d8c4e0b612
--- a/SelectionInTreeView.st	Thu Aug 07 15:29:28 1997 +0200
+++ b/SelectionInTreeView.st	Mon Aug 11 13:01:26 1997 +0200
@@ -12,10 +12,11 @@
 
 
 SelectionInListView subclass:#SelectionInTreeView
-	instanceVariableNames:'doubleClickSelectionBlock figuresWidth leftIndent
-		figuresWidthDiv2 figuresInset showLines listOfNodes imageOpened
-		imageClosed imageItem showDirectoryIndicator'
-	classVariableNames:'ImageOpened ImageClosed ImageItem'
+	instanceVariableNames:'doubleClickSelectionBlock figuresWidth showLines listOfNodes
+		imageOpened imageClosed imageItem imageInset textInset
+		openIndicator closeIndicator showDirectoryIndicator
+		indicatorWidthDiv2 indicatorHeightDiv2'
+	classVariableNames:'ImageOpened ImageClosed ImageItem OpenIndicator CloseIndicator'
 	poolDictionaries:''
 	category:'Views-Text'
 !
@@ -126,10 +127,24 @@
 
 !SelectionInTreeView class methodsFor:'constants'!
 
-figuresInset
-    "returns horizontal right and left inset of a figure
+shownIndicatorInset
+    "returns the additional inset used when setting directory indication to enabled
     "
-  ^ 2
+  ^ 4
+
+
+! !
+
+!SelectionInTreeView class methodsFor:'default images'!
+
+closeIndicator
+    CloseIndicator isNil ifTrue:[
+        CloseIndicator := Image fromFile:('xpmBitmaps/plus.xpm').
+    ].
+  ^ CloseIndicator
+"
+CloseIndicator := nil
+"
 !
 
 imageClosed
@@ -164,10 +179,111 @@
 "
 ImageOpened := nil
 "
+!
+
+openIndicator
+    OpenIndicator isNil ifTrue:[
+        OpenIndicator := Image fromFile:('xpmBitmaps/minus.xpm').
+    ].
+  ^ OpenIndicator
+"
+OpenIndicator := nil
+"
+
 ! !
 
 !SelectionInTreeView methodsFor:'accessing'!
 
+nodeAtIndex:anIndex
+    "returns node at an index or nil
+    "
+    (anIndex notNil and:[anIndex ~~ 0 and:[anIndex <= listOfNodes size]]) ifTrue:[
+        ^ listOfNodes at:anIndex
+    ].
+  ^ nil
+!
+
+textInset
+    "get the left inset of the text label
+    "
+    ^ textInset
+!
+
+textInset:anInset
+    "set the left inset of the text label
+    "
+    |inset|
+
+    anInset ~~ textInset ifTrue:[
+        anInset >= 0 ifTrue:[
+            textInset := anInset.
+            self invalidate
+        ] ifFalse:[
+            self error
+        ]
+    ].
+! !
+
+!SelectionInTreeView methodsFor:'accessing-behavior'!
+
+doubleClickSelectionBlock
+    "get the conditionBlock; this block is evaluated before a doubleClick action
+     on a node containg children will be performed. In case of returning false, the
+     doubleClick will not be handled.
+   "
+   ^ doubleClickSelectionBlock
+
+
+!
+
+doubleClickSelectionBlock:aBlock
+    "set the conditionBlock; this block is evaluated before a doubleClick action
+     on a node containg children will be performed. In case of returning false, the
+     doubleClick will not be handled.
+   "
+   doubleClickSelectionBlock := aBlock
+
+
+!
+
+showDirectoryIndicator
+    "returns true if directories has an open/closed indicator
+    "
+  ^ showDirectoryIndicator
+!
+
+showDirectoryIndicator:aState
+    "set or clear open/closed indicator for directories
+    "
+    "show or hide lines
+    "
+    aState ~~ showDirectoryIndicator ifTrue:[
+        (showDirectoryIndicator := aState) ifTrue:[
+            imageInset := imageInset + self class shownIndicatorInset.
+        ] ifFalse:[
+            imageInset := imageInset - self class shownIndicatorInset.
+        ].
+        self invalidate
+    ].
+!
+
+showLines
+    "returns true if lines are shown
+    "
+  ^ showLines
+!
+
+showLines:aState
+    "show or hide lines
+    "
+    aState ~~ showLines ifTrue:[
+        showLines := aState.
+        self invalidate
+    ].
+! !
+
+!SelectionInTreeView methodsFor:'accessing-images'!
+
 imageClosed
     "return the value of the instance variable 'imageClosed' (automatically generated)"
 
@@ -214,76 +330,6 @@
     imageOpened := something.
 
     "Created: 3.7.1997 / 12:34:28 / cg"
-!
-
-list:aList keepSelection:keepSelection
-    |list|
-
-    list := aList.
-
-    list size == 0 ifTrue:[
-        listOfNodes := #()
-    ] ifFalse:[
-        (list first respondsTo:#hasChildren) ifTrue:[
-            listOfNodes := aList.
-            list := listOfNodes collect:[:aNode| aNode name ].
-        ]
-    ].
-    super list:list keepSelection:keepSelection
-! !
-
-!SelectionInTreeView methodsFor:'accessing-behavior'!
-
-doubleClickSelectionBlock
-    "get the conditionBlock; this block is evaluated before a doubleClick action
-     on a node containg children will be performed. In case of returning false, the
-     doubleClick will not be handled.
-   "
-   ^ doubleClickSelectionBlock
-
-
-!
-
-doubleClickSelectionBlock:aBlock
-    "set the conditionBlock; this block is evaluated before a doubleClick action
-     on a node containg children will be performed. In case of returning false, the
-     doubleClick will not be handled.
-   "
-   doubleClickSelectionBlock := aBlock
-
-
-!
-
-showDirectoryIndicator
-    "returns true if directories has an open/closed indicator
-    "
-  ^ showDirectoryIndicator
-!
-
-showDirectoryIndicator:aState
-    "set or clear open/closed indicator for directories
-    "
-    "show or hide lines
-    "
-    aState ~~ showDirectoryIndicator ifTrue:[
-        showDirectoryIndicator := aState.
-        self invalidate
-    ].
-!
-
-showLines
-    "returns true if lines are shown
-    "
-  ^ showLines
-!
-
-showLines:aState
-    "show or hide lines
-    "
-    aState ~~ showLines ifTrue:[
-        showLines := aState.
-        self invalidate
-    ].
 ! !
 
 !SelectionInTreeView methodsFor:'drawing'!
@@ -322,7 +368,7 @@
 
 drawFromVisibleLine:startVisLineNr to:endVisLineNr with:fg and:bg
 
-    |nodeIndex listSize end fontHgDiv2 yBot yTop yCtr
+    |nodeIndex listSize end fontHgDiv2 yBot yTop yCtr xFig2 figInset
      x x1 xFig xStr node level lvl idx image isCollapsable hasChildren radius extent xCross|
 
     nodeIndex := self visibleLineToAbsoluteLine:startVisLineNr.
@@ -336,8 +382,10 @@
 
     nodeIndex isNil ifTrue:[^ self].
     fontHgDiv2 := fontHeight // 2.
-    radius     := figuresWidthDiv2 // 2 - 1.
-    extent     := radius + radius + 1.
+    xFig2  := figuresWidth // 2..
+    radius := xFig2 // 2 - 1.
+    extent := radius + radius + 1.
+    figInset := figuresWidth + imageInset.
 
     self paint:fg on:bg.
 
@@ -353,29 +401,33 @@
 
         (hasChildren := node hasChildren) ifTrue:[ 
             isCollapsable := node isCollapsable.
+        ] ifFalse:[
+            isCollapsable := false
         ].
 
         (lvl := node level) == level ifFalse:[
             level  := lvl.
             xFig   := self xOfFigureNode:node.
             xStr   := self xOfStringNode:node.
-            xCross := xFig + figuresWidthDiv2 - leftIndent.
+            xCross := xFig + xFig2 - figInset.
         ].
 
         showLines ifTrue:[
             (isCollapsable and:[node numberOfChildren ~~ 0]) ifTrue:[
-                x := xFig + figuresWidthDiv2.
+                x := xFig + xFig2.
                 self displayLineFromX:x y:yCtr toX:x y:yBot
             ].
         "/  draw horizontal and vertical line
-            self displayLineFromX:xCross y:yTop toX:xCross y:yCtr.       "/ vertical
+            nodeIndex == 1 ifFalse:[                                    "/ not for root
+                self displayLineFromX:xCross y:yTop toX:xCross y:yCtr.  "/ vertical
+            ].
             self displayLineFromX:xCross y:yCtr toX:xFig   y:yCtr.       "/ horizontal
 
         "/  draw vertical lines
             idx  := nodeIndex.
 
             idx ~~ listSize ifTrue:[
-                x := leftIndent - figuresWidthDiv2.
+                x := figInset - xFig2.
 
                 [(lvl > 0 and:[(idx := idx + 1) <= listSize])] whileTrue:[
                     node := listOfNodes at:idx.
@@ -396,7 +448,12 @@
         self drawLabelIndex:nodeIndex atX:xStr y:yCtr.
 
         (hasChildren and:[showDirectoryIndicator]) ifTrue:[
-            self drawIndicatorX:xCross y:yCtr collapsable:isCollapsable
+            isCollapsable ifTrue:[image := openIndicator]
+                         ifFalse:[image := closeIndicator].
+
+            self displayForm:image
+                           x:(xCross - indicatorWidthDiv2)
+                           y:(yCtr   - indicatorHeightDiv2)
         ].
 
         "/ setup next line
@@ -411,30 +468,6 @@
 
 !
 
-drawIndicatorX:xCtr y:yCtr collapsable:isCollapsable
-    "draw directory indicator; the arguments received are is the center where
-     to draw the indicator
-    "
-    |radius extent|
-
-    radius := figuresWidthDiv2 // 2 - 1.
-    extent := radius + radius + 1.
-
-    isCollapsable ifFalse:[
-        self displayRectangleX:(xCtr - radius)
-                             y:(yCtr - radius)
-                         width:extent
-                        height:extent.
-    ] ifTrue:[
-        self fillRectangleX:(xCtr - radius)
-                          y:(yCtr - radius)
-                      width:extent
-                     height:extent
-    ]
-
-
-!
-
 drawLabelIndex:anIndex atX:x y:yCenter
     "draw text label at x and y centered
     "
@@ -452,6 +485,27 @@
     ]    
 ! !
 
+!SelectionInTreeView methodsFor:'event handling'!
+
+buttonMultiPress:button x:x y:y
+    |node xFig|
+
+"
+    ((button == 1) or:[button == #select]) ifTrue:[
+        (node := self selectedNode) notNil ifTrue:[
+            node hasChildren ifTrue:[
+                xFig := self xOfFigureNode:node.
+
+                (x < xFig and:[x > (xFig - figuresWidth)]) ifTrue:[
+                    ^ self
+                ]
+            ]
+        ]
+    ].
+"
+    super buttonMultiPress:button x:x y:y
+! !
+
 !SelectionInTreeView methodsFor:'initialization'!
 
 fetchDeviceResources
@@ -467,20 +521,40 @@
      images again and again later; returns maximum extent of the images used.
      Could be redefined by subclass
     "
-    |y x t|
+    |y x t inset|
 
-    imageOpened  := (self class imageOpened) onDevice:device.
-    imageClosed  := (self class imageClosed) onDevice:device.
-    imageItem    := (self class imageItem)   onDevice:device.
+    imageOpened    := (self class imageOpened)    onDevice:device.
+    imageClosed    := (self class imageClosed)    onDevice:device.
+    imageItem      := (self class imageItem)      onDevice:device.
+    openIndicator  := (self class openIndicator)  onDevice:device.
+    closeIndicator := (self class closeIndicator) onDevice:device.
 
     y := imageClosed heightOn:self.
     x := imageClosed widthOn:self.
 
     (t := imageOpened heightOn:self) > y ifTrue:[y := t].
     (t := imageOpened widthOn:self)  > x ifTrue:[x := t].
+
+    (t := imageItem   heightOn:self) > y ifTrue:[y := t].
+    (t := imageItem   widthOn:self)  > x ifTrue:[x := t].
+
     (t := imageItem   heightOn:self) > y ifTrue:[y := t].
     (t := imageItem   widthOn:self)  > x ifTrue:[x := t].
 
+    indicatorWidthDiv2  := openIndicator heightOn:self.
+    indicatorHeightDiv2 := openIndicator widthOn:self.
+    inset := self class shownIndicatorInset.
+
+    (t := inset + indicatorWidthDiv2)  > y ifTrue:[y := t].
+    (t := inset + indicatorHeightDiv2) > x ifTrue:[x := t].
+
+    indicatorWidthDiv2  := indicatorWidthDiv2  // 2.
+    indicatorHeightDiv2 := indicatorHeightDiv2 // 2.
+
+    (t := 4 + (closeIndicator heightOn:self)) > y ifTrue:[y := t].
+    (t := 4 + (closeIndicator widthOn:self )) > x ifTrue:[x := t].
+
+
   ^ x @ y
 
 !
@@ -499,11 +573,9 @@
     super initialize.
     showLines := true.
     showDirectoryIndicator := false.
-
-    figuresWidth     := 18.                             "/ default: will change during startup
-    figuresInset     := 2.                              "/ default: will change during startup
-    leftIndent       := figuresWidth + figuresInset.    "/ default: will change during startup
-    figuresWidthDiv2 := figuresWidth // 2.              "/ default: will change during startup
+    textInset    := 2.
+    imageInset   := 0.
+    figuresWidth := 18.                 "/ default: will change during startup
 !
 
 refetchDeviceResources
@@ -512,16 +584,13 @@
     "
     |y extent|
 
-    figuresInset := self class figuresInset.
-    extent       := self fetchImageResources.
+    extent := self fetchImageResources.
 
     extent y > fontHeight ifTrue:[
         fontHeight := extent y.
     ].
 
-    figuresWidth     := extent x.
-    leftIndent       := figuresInset + figuresWidth.
-    figuresWidthDiv2 := figuresWidth // 2.
+    figuresWidth := extent x.
 
 ! !
 
@@ -555,6 +624,24 @@
   ^ #()
 ! !
 
+!SelectionInTreeView methodsFor:'private'!
+
+list:aList keepSelection:keepSelection
+    |list|
+
+    list := aList.
+
+    list size == 0 ifTrue:[
+        listOfNodes := #()
+    ] ifFalse:[
+        (list first respondsTo:#hasChildren) ifTrue:[
+            listOfNodes := aList.
+            list := listOfNodes collect:[:aNode| aNode name ].
+        ]
+    ].
+    super list:list keepSelection:keepSelection
+! !
+
 !SelectionInTreeView methodsFor:'private queries'!
 
 lengthOfLongestLineBetween:firstLine and:lastLine
@@ -647,8 +734,6 @@
                           ifFalse:[ ^ imageOpened ]
     ].
   ^ imageItem
-
-    "Modified: 3.7.1997 / 12:31:48 / cg"
 !
 
 indexOfNode:aNode
@@ -660,14 +745,21 @@
 xOfFigureNode:aNode
     "origin x where to draw the icon
     "
-   ^ ((aNode level-1) * leftIndent) + figuresInset - leftOffset.
+    |level|
+
+    level := aNode level.
+
+    showDirectoryIndicator ifFalse:[
+        level := level - 1
+    ].
+  ^ (level * (imageInset + figuresWidth)) - leftOffset
 
 !
 
 xOfStringNode:aNode
     "origin x where to draw the text( label )
     "
-    ^ (self xOfFigureNode:aNode) + leftIndent
+    ^ (self xOfFigureNode:aNode) + figuresWidth + textInset
 
 ! !
 
@@ -737,5 +829,5 @@
 !SelectionInTreeView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/SelectionInTreeView.st,v 1.12 1997-08-07 13:11:45 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/SelectionInTreeView.st,v 1.13 1997-08-11 11:01:26 ca Exp $'
 ! !