HierarchicalListView.st
changeset 2316 f91a9635462e
parent 2313 6e91bdaac5bc
child 2317 5f44d976c81f
--- a/HierarchicalListView.st	Sat Oct 19 13:36:21 2002 +0200
+++ b/HierarchicalListView.st	Sun Oct 20 14:17:51 2002 +0200
@@ -111,7 +111,7 @@
     list root:item.
 
     top := StandardSystemView new; extent:300@300.
-    sel := ScrollableView for:HierarchicalListView miniScroller:true
+    sel := ScrollableView for:HierarchicalListView miniScrollerH:true
                        origin:0.0@0.0 corner:1.0@1.0 in:top.
 
     sel list:list.
@@ -138,7 +138,7 @@
     list root:item.
 
     top := StandardSystemView new; extent:300@300.
-    sel := ScrollableView for:HierarchicalListView miniScroller:true
+    sel := ScrollableView for:HierarchicalListView miniScrollerH:true
                        origin:0.0@0.0 corner:1.0@1.0 in:top.
 
     sel list:list.
@@ -167,6 +167,30 @@
     top open.
                                                                         [exEnd]
 
+                                                                        [exBegin]
+    |top sel list item|
+
+    list := HierarchicalList new.
+    item := HierarchicalItem::Example labeled:'Root Item'.
+
+    item expand.
+    list showRoot:false.
+    list root:item.
+
+    top := StandardSystemView new; extent:300@300.
+    sel := ScrollableView for:HierarchicalListView miniScrollerH:true
+                       origin:0.0@0.0 corner:1.0@1.0 in:top.
+
+    sel list:list.
+    sel multipleSelectOk:true.
+    sel alignTextRight:true.
+    sel doubleClickAction:[:i| (list at:i) toggleExpand ].
+    sel   indicatorAction:[:i| (list at:i) toggleExpand ].
+
+    top open.
+                                                                        [exBegin]
+
+
 "
 ! !
 
@@ -522,8 +546,9 @@
      yB "{ Class:SmallInteger }"
     |
 
+    item := list at:aLnNr ifAbsent:nil.
+
     (arg == #icon or:[arg == #hierarchy]) ifFalse:[
-        item := list at:aLnNr ifAbsent:nil.
         item isNil ifTrue:[^ self].
 
         super lineChangedAt:aLnNr with:arg.
@@ -540,6 +565,24 @@
         ].
         ^ self
     ].
+
+    (alignTextRight and:[arg == #hierarchy]) ifTrue:[
+        "/ must test whether alignTextRightX is enough
+        (item notNil and:[item isExpanded and:[item hasChildren]]) ifTrue:[        
+            x0 := self xOfFigureLevel:(item level + 2).
+
+            alignTextRightX < x0 ifTrue:[
+                alignTextRightX := x0.
+                shown ifTrue:[ self invalidate ].
+
+                widthOfContents notNil ifTrue:[
+                    widthOfContents := alignTextRightX + maxWidthOfText.
+                    self contentsChanged.
+                ].
+                ^ self.
+            ]
+        ]
+    ].
     shown ifFalse:[^ self].
 
     yB := height - margin.
@@ -658,8 +701,7 @@
 drawElementsFrom:start to:stop x:xLeft y:yT w:w
     "draw the items between start to stop without clearing the background
     "
-    |item prevItem parent icon showIndc showIcon showText nxtPrnt iconHeight
-     iconExtent
+    |item prevItem parent icon showIndc showIcon showText nxtPrnt extent
      yTop      "{ Class:SmallInteger }"
      yCtr      "{ Class:SmallInteger }"
      yBot      "{ Class:SmallInteger }"
@@ -667,7 +709,6 @@
      xIndc     "{ Class:SmallInteger }"
      xIcon     "{ Class:SmallInteger }"
      xText     "{ Class:SmallInteger }"
-     xDeltaIT  "{ Class:SmallInteger }"
      xL        "{ Class:SmallInteger }"
      xR        "{ Class:SmallInteger }"
      height    "{ Class:SmallInteger }"
@@ -678,8 +719,6 @@
      offIndcX  "{ Class:SmallInteger }"
      offIndcY  "{ Class:SmallInteger }"
      offIconX  "{ Class:SmallInteger }"
-     iconWidth "{ Class:SmallInteger }"
-     iconRgtX  "{ Class:SmallInteger }"
     |
     widthLvl := self parentToChildInset.
     insetTxt := textStartLeft + imageWidth.
@@ -697,10 +736,10 @@
     indicatorAction notNil ifTrue:[
         offIndcX := offIndcY := 0.
         openIndicator notNil ifTrue:[
-            iconExtent     := openIndicator extent // 2.
+            extent   := openIndicator extent // 2.
             offIndcX := imageWidth // 2 - widthLvl.
-            offIndcX := offIndcX - iconExtent x.
-            offIndcY := iconExtent y.
+            offIndcX := offIndcX - extent x.
+            offIndcY := extent y.
         ]
     ].
 
@@ -728,72 +767,25 @@
             xIcon  := prevItem == parent ifTrue:[xIcon + widthLvl]
                                         ifFalse:[item level * widthLvl + offIconX].
 
-
             alignTextRight ifFalse:[
                 xText    := xIcon + insetTxt.
-                showText := xText < xR.
+                showText := (xText < xR).
             ].
-            showIcon := xIcon < xR and:[xText > xL].
+            showIcon := (xIcon < xR and:[xText > xL]).
 
             indicatorAction notNil ifTrue:[
-                xIndc := xIcon + offIndcX.
+                xIndc    := xIcon + offIndcX.
+                showIndc := (xIcon > xL and:[xIndc < xR]).
 
-                (xIcon > xL and:[xIndc < xR]) ifTrue:[
+                showIndc ifTrue:[
                     showIndc := parent notNil or:[showLeftIndicators]
-                ] ifFalse:[
-                    showIndc := false
                 ]
             ]
         ].
 
-        (showIcon and:[(icon := self figureFor:item) notNil]) ifTrue:[
-            iconWidth  := icon width.
-            iconHeight := icon height.
-
-            iconRgtX   := xIcon + iconWidth.
-            xDeltaIT   := xText - textStartLeft - iconRgtX.
-            xDeltaIT < 0 ifTrue:[
-                alignTextRightX := alignTextRightX - xDeltaIT.
-
-                widthOfContents notNil ifTrue:[
-                    alignTextRight ifFalse:[ |old|
-                        iconWidth  := iconWidth + 1 // 2 * 2.
-                        widthLvl   := (iconWidth - imageWidth) max:2.
-                        imageWidth := imageWidth + widthLvl.
-
-                        list criticalDo:[
-                            xL := 1.
-                            list do:[:el| xL := xL max:(el level) ].
-                            list showRoot ifFalse:[ xL := xL - 1 ].
-                            widthOfContents := widthOfContents + (xL * widthLvl)
-                        ].
-                    ] ifTrue:[
-                        widthOfContents := alignTextRightX + maxWidthOfText
-                    ].
-                    
-                    widthLvl := self xOfStringLevel:(item level).
-                    xText    := item widthOn:self.
-                    xText > maxWidthOfText ifTrue:[ maxWidthOfText := xText ].
-
-                    widthOfContents := (widthLvl + xText) max:widthOfContents.
-                ].
-                (constantHeight notNil and:[ iconHeight >= constantHeight ]) ifTrue:[
-                    constantHeight := iconHeight + lineSpacing.
-                    self recomputeHeightOfContents.
-                ].
-                self contentsChanged.
-                StopRedrawSignal raise
-            ].
-
-            iconRgtX > xL ifTrue:[
-                (constantHeight notNil and:[ iconHeight >= constantHeight ]) ifTrue:[
-                    constantHeight := iconHeight + lineSpacing.
-
-                    self recomputeHeightOfContents.
-                    self contentsChanged.
-                    StopRedrawSignal raise
-                ].
-                icon displayOn:self x:xIcon y:(yCtr - (iconHeight // 2))
+        (showIcon and:[(icon := self validateDrawableIconFor:item) notNil]) ifTrue:[
+            (xIcon + icon width) > xL ifTrue:[
+                icon displayOn:self x:xIcon y:(yCtr - (icon height // 2))
             ]
         ].
 
@@ -801,10 +793,10 @@
             self drawLabelAt:anIndex x:xText y:yTop h:height
         ].
         (showIndc and:[item hasIndicator]) ifTrue:[
-            icon := item isExpanded ifTrue:[openIndicator] ifFalse:[closeIndicator].
-            icon notNil ifTrue:[
-                icon displayOn:self x:xIndc y:(yCtr - offIndcY)
-            ]
+            item isExpanded ifTrue:[icon := openIndicator ]
+                           ifFalse:[icon := closeIndicator].
+
+            icon displayOn:self x:xIndc y:(yCtr - offIndcY)
         ].
         prevItem := item.
     ]
@@ -980,6 +972,58 @@
         ]
     ].
     self mask:nil.
+!
+
+validateDrawableIconFor:anItem
+    "returns the icon to be drawn for an item or nil
+     test the extent of the icopn; on error an exception is raised
+    "
+    |width needMore icon maxLevel startOfText|
+
+    icon := self figureFor:anItem.
+    icon isNil ifTrue:[^ nil].
+
+    width := icon width.
+
+    (constantHeight notNil and:[icon height > constantHeight]) ifTrue:[
+        constantHeight := icon height + lineSpacing.
+        self recomputeHeightOfContents.
+
+        width <= imageWidth ifTrue:[
+            self contentsChanged.
+            StopRedrawSignal raise
+        ].
+    ] ifFalse:[
+        width <= imageWidth ifTrue:[ ^ icon ].
+    ].
+
+    needMore   := width - imageWidth max:2.
+    imageWidth := imageWidth + needMore.
+    maxLevel   := 1.
+
+    list criticalDo:[
+        list do:[:el| maxLevel := maxLevel max:(el level) ].
+    ].
+    alignTextRightX := alignTextRightX max:(self xOfFigureLevel:(maxLevel + 1)).
+
+    widthOfContents notNil ifTrue:[
+        alignTextRight ifTrue:[
+            widthOfContents := alignTextRightX + maxWidthOfText
+        ] ifFalse:[
+            list showRoot ifFalse:[ maxLevel := maxLevel - 1 ].
+            widthOfContents := widthOfContents + (maxLevel * needMore)
+        ].
+        width           := anItem widthOn:self.
+        startOfText     := self xOfStringLevel:(anItem level).
+        widthOfContents := widthOfContents max:(startOfText + width).
+
+        width > maxWidthOfText ifTrue:[
+            maxWidthOfText := width
+        ].
+    ].
+    self contentsChanged.
+    StopRedrawSignal raise.
+  ^ icon
 ! !
 
 !HierarchicalListView methodsFor:'event handling'!
@@ -1088,7 +1132,7 @@
     "fetch device colors and ..., to avoid reallocation at redraw time;
      *** called after a create or snapin to fetch all device resources
     "
-    |image|
+    |image defaultWidth|
 
     super fetchResources.
 
@@ -1096,7 +1140,7 @@
     lineColor      := lineColor onDevice:device.
     openIndicator  := self imageOnDevice:openIndicator.
     closeIndicator := self imageOnDevice:closeIndicator.
-    imageWidth     := 4.
+    defaultWidth   := imageWidth.
 
     icons keysAndValuesDo:[:aKey :anImage|
         anImage isNil ifTrue:[
@@ -1107,7 +1151,7 @@
             imageWidth := image width max:imageWidth.
         ]
     ].
-    imageWidth      := imageWidth + 1 // 2 * 2.
+    imageWidth      := (imageWidth + 1 // 2 * 2) max:defaultWidth.
     alignTextRightX := imageWidth + 20 max:alignTextRightX.
 ! !
 
@@ -1136,7 +1180,7 @@
     useDefaultIcons    := true.
     showLines          := true.
     imageInset         := 4.
-    imageWidth         := 8.    "/ default
+    imageWidth         := 16. "/ default
     alignTextRight     := false.
     alignTextRightX    := 8.
     maxWidthOfText     := 0.
@@ -1266,27 +1310,36 @@
      itemW     "{ Class: SmallInteger }"
     |
     width  := 20.
+    level  := 1.
+    pprnt  := 4711.  "/ force a computation
+    deltaX := self parentToChildInset.
 
     alignTextRight ifTrue:[
         firstLine to:lastLine do:[:idx|
-            item  := list at:idx ifAbsent:nil.
+            item := list at:idx ifAbsent:nil.
+
+            item notNil ifTrue:[
+                width := (item widthOn:self) max:width.
 
-            item isNil ifTrue:[
-                  maxWidthOfText := maxWidthOfText max:width.
-                ^ alignTextRightX + width
+                nprnt := item parent.
+                nprnt ~~ pprnt ifTrue:[
+                    level := item level max:level.
+                    pprnt := nprnt.
+                ].
             ].
-            width := (item widthOn:self) max:width.
         ].
         maxWidthOfText := maxWidthOfText max:width.
-      ^ alignTextRightX + width
+        startX         := self xOfFigureLevel:(level + 1).
+
+        alignTextRightX < startX ifTrue:[
+            shown ifTrue:[ self invalidate].
+            alignTextRightX := startX
+        ].
+        ^ alignTextRightX + width
     ].
 
-    pprnt  := 4711.  "/ force a computation
     pitem  := 4712.  "/ force a computation
-    deltaX := self parentToChildInset.
-
-    startX := self xOfStringLevel:1.
-    startX := startX + (viewOrigin x).
+    startX := (self xOfStringLevel:1) + (viewOrigin x).
     textX  := 0.
     level  := 1.
 
@@ -1352,10 +1405,11 @@
     "
     |item xLft xRgt lvWidth level vwOrgX xInset|
 
+    alignTextRight ifTrue:[^ viewOrigin x ].
+
     aLnrNr == 1 ifTrue:[^ 0].
 
     vwOrgX := viewOrigin x.
-    alignTextRight ifTrue:[ ^ vwOrgX ].
 
     item := list at:aLnrNr ifAbsent:nil.
     item isNil ifTrue:[ ^ vwOrgX ].
@@ -1383,6 +1437,8 @@
     "
     |newY item y0 newX|
 
+    alignTextRight ifTrue:[^ self].
+
     (shown and:[aLnrNr notNil]) ifFalse:[^ self].
 
     aLnrNr <= 1 ifTrue:[
@@ -1422,5 +1478,5 @@
 !HierarchicalListView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/HierarchicalListView.st,v 1.60 2002-10-18 09:08:05 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/HierarchicalListView.st,v 1.61 2002-10-20 12:17:51 ca Exp $'
 ! !