support of multiple select:rows
authorca
Fri, 07 Nov 1997 14:27:53 +0100
changeset 607 a5e0c2bf1370
parent 606 fefb91a25597
child 608 0d8d910768af
support of multiple select:rows
DSVColumnView.st
DSVLabelView.st
DataSetColumn.st
DataSetView.st
--- a/DSVColumnView.st	Mon Nov 03 16:19:36 1997 +0100
+++ b/DSVColumnView.st	Fri Nov 07 14:27:53 1997 +0100
@@ -14,15 +14,17 @@
 
 
 View subclass:#DSVColumnView
-	instanceVariableNames:'editValue editView selectedColIndex selectedRowIndex rowHeight
-		columnDescriptors viewOrigin registererImages list fgColor canFit
-		listSizeChanged beDependentOfRows has3Dsepartors bgColor
-		hgLgFgColor hgLgBgColor actionBlock doubleClickActionBlock
-		separatorLightColor separatorDarkColor verticalSpacing
-		horizontalSpacing'
+	instanceVariableNames:'editValue editView multipleSelectOk selectedColIndex
+		selectedRowIndex rowHeight columnDescriptors viewOrigin
+		registererImages list fgColor canFit separatorSize
+		listSizeChanged beDependentOfRows bgColor hgLgFgColor hgLgBgColor
+		actionBlock doubleClickActionBlock separatorLightColor
+		separatorDarkColor verticalSpacing horizontalSpacing
+		toggleOnButton toggleOffButton rowSelectorButton comboViewButton'
 	classVariableNames:'DefaultForegroundColor DefaultBackgroundColor
 		DefaultHilightForegroundColor DefaultHilightBackgroundColor
-		DefaultSeparatorDarkColor DefaultSeparatorLightColor'
+		DefaultSeparatorDarkColor DefaultSeparatorLightColor
+		DefaultRowSelectorForm'
 	poolDictionaries:''
 	category:'Views-DataSet'
 !
@@ -81,6 +83,31 @@
 
 !DSVColumnView class methodsFor:'defaults'!
 
+defaultRowSelectorForm
+
+    DefaultRowSelectorForm isNil ifTrue:[
+        DefaultRowSelectorForm := Form
+                          width:8
+                         height:11
+                      fromArray:#[2r01000000
+                                  2r01100000
+                                  2r01110000
+                                  2r01111000
+                                  2r01111100
+                                  2r01111110
+                                  2r01111100
+                                  2r01111000
+                                  2r01110000
+                                  2r01100000
+                                  2r01000000]
+                             on:Display.
+
+        DefaultRowSelectorForm := DefaultRowSelectorForm asImage.
+    ].
+    ^ DefaultRowSelectorForm
+
+!
+
 horizontalSpacing
     ^ 4
 
@@ -100,6 +127,7 @@
     DefaultHilightBackgroundColor := StyleSheet colorAt:'selection.hilightBackgroundColor' default:(Color veryLightGrey).
     DefaultSeparatorDarkColor     := DefaultShadowColor ? (Color grayPercent:40).
     DefaultSeparatorLightColor    := DefaultLightColor  ? (Color grayPercent:75).
+
 "
 self updateStyleCache.
 "
@@ -115,19 +143,13 @@
 !DSVColumnView methodsFor:'accessing'!
 
 action:aOneArgAction
+    "set the action block to be performed on select
+    "
     actionBlock := aOneArgAction
 
 
 !
 
-doubleClickAction:aOneArgAction
-    doubleClickActionBlock := aOneArgAction
-
-
-! !
-
-!DSVColumnView methodsFor:'accessing behavior'!
-
 beDependentOfRows
     "make myself dependent of any row; in this case any change notification
      raised by a row is catched and the cell identified by the 'readSelector'
@@ -152,12 +174,79 @@
             self do:[:aRow| aRow removeDependent:self]
         ]
     ].
+!
+
+doubleClickAction:aOneArgAction
+    "set the action block to be performed on doubleclick
+    "
+    doubleClickActionBlock := aOneArgAction
+
+
+!
+
+multipleSelectOk
+    "allow/disallow multiple row selections; the default is false
+    "
+    ^ multipleSelectOk
+!
+
+multipleSelectOk:aState
+    "allow/disallow multiple row selections; the default is false
+    "
+    aState == multipleSelectOk ifFalse:[
+        multipleSelectOk := aState.
+        self deselect
+    ]
+! !
+
+!DSVColumnView methodsFor:'accessing buttons'!
+
+comboViewButton
+    "returns the bitmap of a comboView button
+    "
+    comboViewButton isNil ifTrue:[
+        comboViewButton := (Image fromFile:'dsv_comboList.xpm') on:device.
+        comboViewButton clearMaskedPixels.
+    ].
+
+    ^ comboViewButton
+!
+
+rowSelectorButton
+    "returns the bitmap of a selected row
+    "
+    rowSelectorButton isNil ifTrue:[
+        rowSelectorButton := (self class defaultRowSelectorForm) on:device
+    ].
+    ^ rowSelectorButton
+!
+
+toggleOffButton
+    "returns the bitmap of a disabled toggle
+    "
+    toggleOffButton isNil ifTrue:[
+        toggleOffButton := (Image fromFile:'dsv_checkTgOff.xpm') on:device.
+        toggleOffButton clearMaskedPixels.
+    ].
+
+    ^ toggleOffButton
+!
+
+toggleOnButton
+    "returns the bitmap of an enabled toggle
+    "
+    toggleOnButton isNil ifTrue:[
+        toggleOnButton := (Image fromFile:'dsv_checkTgOn.xpm') on:device.
+        toggleOnButton clearMaskedPixels.
+    ].
+
+    ^ toggleOnButton
 ! !
 
 !DSVColumnView methodsFor:'accessing columns'!
 
 columnAt:anIndex
-    "get the column at an index
+    "returns the column at an index
     "
     ^ columnDescriptors at:anIndex
 !
@@ -165,11 +254,16 @@
 columnDescriptors:colDesc
     "set the columnDescriptors
     "
+    |id|
+
     self setSelectColIndex:0 rowIndex:0.
 
     colDesc size ~~ 0 ifTrue:[
+        id := 0.
+
         columnDescriptors := colDesc collect:[:aCol|
-            DataSetColumn on:self description:aCol
+            id := id + 1.
+            DataSetColumn new on:self description:aCol columnNumber:id.
         ]
     ] ifFalse:[
         columnDescriptors := #()
@@ -193,14 +287,14 @@
 !
 
 firstColumn
-    "get the first column
+    "returns the first column
     "
     ^ columnDescriptors at:1
 
 !
 
 lastColumn
-    "get the last column
+    "returns the last column
     "
     ^ columnDescriptors last
 
@@ -215,7 +309,7 @@
 !
 
 at:aRowNr ifAbsent:exceptionBlock
-    "return the element at a aRowNr. If the index is invalid, return the
+    "return the row at a aRowNr. If the index is invalid, return the
      result of evaluating the exceptionblock
     "
     ^ list at:aRowNr ifAbsent:exceptionBlock
@@ -227,10 +321,8 @@
     beDependentOfRows ifTrue:[
         (list at:aRowNr) removeDependent:self.
         aRow addDependent:self
-        
-    ] ifFalse:[
-        list at:aRowNr put:aRow
     ].
+    list at:aRowNr put:aRow.
     self redrawRowAt:aRowNr.
     ^ aRow.
 !
@@ -362,14 +454,22 @@
 
 !
 
-has3Dsepartors
-    ^ has3Dsepartors
+has3Dseparators
+    "returns true if shown in 3D mode
+    "
+    ^ separatorSize ~~ 1
 !
 
-has3Dsepartors:aBool
+has3Dseparators:aBool
+    "enable or disable 3D mode
+    "
+    |newSepSize|
 
-    aBool ~~ has3Dsepartors ifTrue:[
-        has3Dsepartors := aBool.
+    newSepSize := aBool ifTrue:[4] ifFalse:[1].
+
+    newSepSize ~~ separatorSize ifTrue:[
+        separatorSize := newSepSize.
+        
         self columnsDo:[:aCol| aCol invalidate ].
         self preferredExtentChanged.
 
@@ -384,10 +484,14 @@
 !
 
 hgLgBgColor
+    "returns the background color of a selected row
+    "
     ^ hgLgBgColor
 !
 
 hgLgFgColor
+    "returns the foreground color of a selected row
+    "
     ^ hgLgFgColor
 !
 
@@ -407,12 +511,16 @@
 !
 
 separatorDarkColor
+    "returns the dark color used for drawing a shadowed separator (3D)
+    "
     ^ separatorDarkColor
 
 
 !
 
 separatorLightColor
+    "returns the light color used for drawing a shadowed separator (3D)
+    "
     ^ separatorLightColor
 
 
@@ -466,8 +574,20 @@
     beDependentOfRows ifTrue:[
         aRow addDependent:self.
     ].
-    (aRowNr <= selectedRowIndex) ifTrue:[
-        selectedRowIndex := selectedRowIndex + 1.
+
+    (y0 := self numberOfSelections) ~~ 0 ifTrue:[
+        y0 == 1 ifTrue:[
+            (y0 := self firstIndexSelected) >= aRowNr ifTrue:[
+                y0 := y0 + 1.
+                multipleSelectOk ifFalse:[
+                    selectedRowIndex := y0
+                ] ifTrue:[
+                    selectedRowIndex at:1 put:y0
+                ]
+            ]
+        ] ifFalse:[
+            self deselect
+        ]
     ].
     y0 := (aRowNr - 1) * rowHeight.
 
@@ -530,15 +650,20 @@
     |y0 y1 h dY oY yB noRedraw row|
 
     row := list at:aRowNr ifAbsent:[^ self subscriptBoundsError:aRowNr].
+    list isArray ifTrue:[list := list asOrderedCollection].
 
-    list isArray ifTrue:[
-        list := list asOrderedCollection.
-    ].
-    selectedRowIndex == aRowNr ifTrue:[
-        self selectColIndex:0 rowIndex:0
-    ] ifFalse:[
-        selectedRowIndex > aRowNr ifTrue:[
-            selectedRowIndex := selectedRowIndex - 1
+    (y0 := self numberOfSelections) ~~ 0 ifTrue:[
+        y0 == 1 ifTrue:[
+            (y0 := self firstIndexSelected) > aRowNr ifTrue:[
+                y0 := y0 - 1.
+                multipleSelectOk ifFalse:[
+                    selectedRowIndex := y0
+                ] ifTrue:[
+                    selectedRowIndex at:1 put:y0
+                ]
+            ]
+        ] ifFalse:[
+            self deselect
         ]
     ].
     y1 := aRowNr * rowHeight.
@@ -664,17 +789,68 @@
 
 !DSVColumnView methodsFor:'event handling'!
 
+buttonMotion:buttonMask x:x y:y
+    "mouse-move while button was pressed - handle multiple selection changes
+    "
+    |idx size scr|
+
+    self sensor ctrlDown ifTrue:[^ self ].
+
+    (multipleSelectOk and:[selectedColIndex == 0 and:[selectedRowIndex notNil]]) ifFalse:[
+        ^ self
+    ].
+    "is it the select or 1-button ?"
+
+    (device buttonMotionMask:buttonMask includesButton:#select) ifFalse:[
+        (device buttonMotionMask:buttonMask includesButton:1) ifFalse:[
+            ^ self
+        ].
+    ].
+
+    scr := 0.
+
+    y > height ifTrue:[
+        scr := rowHeight.
+        idx := self yVisibleToRowNr:(height + rowHeight).
+    ] ifFalse:[
+        y < 0 ifTrue:[
+            scr := rowHeight negated.
+            idx := self yVisibleToRowNr:scr.
+        ] ifFalse:[
+            idx := self yVisibleToRowNr:y.
+        ]
+    ].
+
+    (idx isNil or:[idx < 1]) ifTrue:[^ self].
+        
+    (self isInSelection:idx) ifTrue:[
+        ^ self
+    ].
+
+    selectedRowIndex := selectedRowIndex asOrderedCollection.
+    selectedRowIndex add:idx.
+
+    scr == 0 ifTrue:[
+        self redrawRowAt:idx
+    ] ifFalse:[
+        self scrollTo:(viewOrigin + (0 @ scr)) redraw:true
+    ].
+    self selectionChanged.    
+!
+
 buttonMultiPress:button x:x y:y
     "a button was pressed twice - handle doubleclick here
     "
     ((button == 1) or:[button == #select]) ifFalse:[
         ^ super buttonMultiPress:button x:x y:y
     ].
-    selectedRowIndex == (self yVisibleToRowNr:y) ifTrue:[
-        (     selectedColIndex == 0
-          or:[selectedColIndex == (self xVisibleToColNr:x)]
-        ) ifTrue:[
-            self doubleClicked
+    self numberOfSelections == 1 ifTrue:[
+        self firstIndexSelected == (self yVisibleToRowNr:y) ifTrue:[
+            (     selectedColIndex == 0
+              or:[selectedColIndex == (self xVisibleToColNr:x)]
+            ) ifTrue:[
+                self doubleClicked
+            ]
         ]
     ]
 
@@ -686,35 +862,51 @@
 buttonPress:button x:x y:y
     "a button was pressed - handle selection here
     "
-    |rowNr colNr menu col|
+    |rowNr colNr menu col sz|
 
     (     (rowNr := self yVisibleToRowNr:y) notNil
      and:[(colNr := self xVisibleToColNr:x) notNil]
     ) ifTrue:[
-        ((button == 2) or:[button == #menu]) ifTrue:[           "/ menu for cell
-            selectedRowIndex == rowNr ifTrue:[
-
-                (selectedColIndex == 0) ifTrue:[                "/ row selected
-                    col := columnDescriptors detect:[:c| c rendererType == #rowSelector]
-                                             ifNone:[nil].
-
-                    col notNil ifTrue:[
-                        menu := col menuForRow:(self selectedRow).
-                        menu notNil ifTrue:[
-                            ^ menu startUp
-                        ]
-                    ].
-                    ^ self
-                ].
-                selectedColIndex == colNr ifTrue:[
-                    menu := self selectedColumn menuForRow:(self selectedRow).
+        ((button == 2) or:[button == #menu]) ifTrue:[
+            (self numberOfSelections == 1 and:[self firstIndexSelected == rowNr]) ifTrue:[
+                selectedColIndex == colNr ifTrue:[                          "/ cell menu ?
+                    menu := self selectedColumn menuForRow:(self at:rowNr).
                     menu notNil ifTrue:[
                         ^ menu startUp
                     ].
                 ].
-            ].
+                col := columnDescriptors detect:[:c| c rendererType == #rowSelector]
+                                         ifNone:[nil].
+
+                col notNil ifTrue:[                                         "/ row  menu ?
+                    menu := col menuForRow:(self at:rowNr).
+                    menu notNil ifTrue:[
+                        ^ menu startUp
+                    ]
+                ]                                                           "/ view menu
+            ]
         ] ifFalse:[
-            ((button == 1) or:[button == #select]) ifTrue:[     "/ selection change
+            ((button == 1) or:[button == #select]) ifTrue:[
+                (multipleSelectOk not or:[self sensor ctrlDown not]) ifFalse:[
+                    selectedColIndex ~~ 0 ifTrue:[
+                        colNr := 0
+                    ] ifFalse:[
+                        (sz := self numberOfSelections == 0) ifFalse:[
+                            (self isInSelection:rowNr) ifTrue:[
+                                sz == 1 ifTrue:[
+                                    self selectColIndex:0 rowIndex:nil.
+                                    ^ self sensor flushMotionEventsFor:self.
+                                ].
+                                selectedRowIndex remove:rowNr.
+                            ] ifFalse:[
+                                selectedRowIndex add:rowNr
+                            ].
+                            self redrawRowAt:rowNr.
+                            self selectionChanged.
+                          ^ self sensor flushMotionEventsFor:self.
+                        ]
+                    ]
+                ].
                 ^ self selectColIndex:colNr rowIndex:rowNr
             ]
         ]
@@ -748,7 +940,7 @@
     "handle a double click
     "
     (doubleClickActionBlock notNil and:[self hasSelection]) ifTrue:[
-        doubleClickActionBlock value:selectedRowIndex
+        doubleClickActionBlock value:(self firstIndexSelected)
     ].
 !
 
@@ -760,7 +952,7 @@
                           #ScrollUp #ScrollDown
                           #CursorUp #CursorDown #CursorRight #CursorLeft)>
 
-    |sensor n max idx col|
+    |sensor n max idx col selRowNr|
 
     (key == #PreviousPage) ifTrue: [^ self pageUp].
     (key == #NextPage)     ifTrue: [^ self pageDown].
@@ -788,7 +980,8 @@
         ].
         ^ self scrollDown:(n * self verticalScrollStep)
     ].
-    self hasSelection ifFalse:[^ self].
+    self numberOfSelections == 1 ifFalse:[^ self].
+    selRowNr := self firstIndexSelected.
 
     key == #Return ifTrue:[
         ^ self doubleClicked
@@ -804,9 +997,9 @@
         (n := n \\ max) == 0 ifTrue:[^ self ].
 
         key == #CursorUp ifTrue:[
-            (n := selectedRowIndex - n) <= 0  ifTrue:[n := max + n]
+            (n := selRowNr - n) <= 0  ifTrue:[n := max + n]
         ] ifFalse:[
-            (n := selectedRowIndex + n) > max ifTrue:[n := n - max]
+            (n := selRowNr + n) > max ifTrue:[n := n - max]
         ].
         ^ self selectColIndex:selectedColIndex rowIndex:n.
     ].
@@ -820,25 +1013,23 @@
         ] ifFalse:[
             n := 1 + (sensor compressKeyPressEventsWithKey:key).
         ].
-        (n := n \\ (self numberOfSelectableColumns)) == 0 ifTrue:[^ self ].
-
         idx := selectedColIndex.
         max := self numberOfColumns.
 
         key == #CursorLeft ifTrue:[
             [n ~~ 0] whileTrue:[
                 (idx := idx - 1) == 0 ifTrue:[idx := max].
-                (self columnAt:idx) canSelect ifTrue:[n := n - 1]
+                ((self columnAt:idx) canSelect:selRowNr) ifTrue:[n := n - 1]
             ]
         ] ifFalse:[
             [n ~~ 0] whileTrue:[
                 idx == max ifTrue:[idx := 1]
                               ifFalse:[idx := idx + 1].
-                (self columnAt:idx) canSelect ifTrue:[n := n - 1]
+                ((self columnAt:idx) canSelect:selRowNr) ifTrue:[n := n - 1]
             ]
         ].
 
-        ^ self selectColIndex:idx rowIndex:selectedRowIndex.
+        ^ self selectColIndex:idx rowIndex:selRowNr.
     ].
     key isCharacter ifFalse:[
         ^ self
@@ -848,14 +1039,14 @@
 
     "/ search forward
     idx := col findRowNrStartingWithChar:key
-                                   start:(selectedRowIndex + 1)
+                                   start:(selRowNr + 1)
                                     stop:(self numberOfRows).
 
     idx == 0 ifTrue:[
         "/ search from begin
         idx := col findRowNrStartingWithChar:key
                                        start:1
-                                        stop:(selectedRowIndex - 1).
+                                        stop:(selRowNr - 1).
     ].
     idx ~~ 0 ifTrue:[
         self selectColIndex:selectedColIndex rowIndex:idx.
@@ -919,7 +1110,7 @@
 !DSVColumnView methodsFor:'initialization'!
 
 create
-    "set foreground color
+    "set color on device
     "
     super create.
     fgColor     := fgColor     on:device.
@@ -941,8 +1132,8 @@
 !
 
 initStyle
-    "setup viewStyle specifics"
-
+    "setup colors
+    "
     super initStyle.
 
     DefaultForegroundColor isNil ifTrue:[
@@ -961,14 +1152,13 @@
     "
     super initialize.
 
-    viewOrigin := 0@0.
-    font       := font on:device.
-    "/ self bitGravity:#NorthWest.
-    rowHeight  := font height.
-    selectedRowIndex := 0.
-    selectedColIndex := 0.
-    registererImages := IdentityDictionary new.
-    has3Dsepartors   := false.
+    viewOrigin        := 0@0.
+    font              := font on:device.
+    rowHeight         := font height.
+    multipleSelectOk  := false.
+    selectedRowIndex  := selectedColIndex  := 0.
+    registererImages  := IdentityDictionary new.
+    separatorSize     := 1.
     columnDescriptors := #().
     beDependentOfRows := false.
     listSizeChanged   := false.
@@ -977,20 +1167,27 @@
 !
 
 realize
-    "recompute contents; set selection
+    "recompute contents and fit columns to view
     "
-    |rowNr colNr|
-
+    self  bitGravity:#NorthWest.
     self  recomputeHeightOfContents.
     super realize.
+    self  fitColumns.
 
-    rowNr := selectedRowIndex.
-    colNr := selectedColIndex.
-    selectedColIndex := 0.
-    selectedRowIndex := 0.
-    self fitColumns.
-    self setSelectColIndex:colNr rowIndex:rowNr.
-    self bitGravity:#NorthWest.
+! !
+
+!DSVColumnView methodsFor:'obsolete'!
+
+has3Dsepartors
+    "shouldn't be used any more
+    "
+    ^ self has3Dseparators
+!
+
+has3Dsepartors:aBool
+    "shouldn't be used any more
+    "
+    self has3Dseparators:aBool
 
 ! !
 
@@ -1033,7 +1230,7 @@
 
     self hasSelection ifTrue:[
         editView notNil ifTrue:[
-            editView width:(self selectedColumn width - 1 - self separatorSize)
+            editView width:(self selectedColumn width - separatorSize)
         ].
         self scrollToSelection.
     ].
@@ -1059,8 +1256,8 @@
     |x y|
 
     editView notNil ifTrue:[
-        y := 1 + (self yVisibleOfRowNr:selectedRowIndex).
-        x := 1 + (self xVisibleOfColNr:selectedColIndex).
+        y := self yVisibleOfRowNr:(self firstIndexSelected).
+        x := self xVisibleOfColNr:(self selectedColIndex).
 
         editView origin:(x @ y).
     ].
@@ -1079,6 +1276,8 @@
 !
 
 xVisibleToColNr:x
+    "returns the column number assigned to a physical x or nil
+    "
     |x0 nr|
 
     x0 := x + viewOrigin x - margin.
@@ -1100,7 +1299,7 @@
 !
 
 yVisibleToRowNr:y
-    "returns row number or nil
+    "returns the row number assigned to a physical y or nil
     "
     |y0|
 
@@ -1145,16 +1344,6 @@
 
 !
 
-numberOfSelectableColumns
-    "returns number of selectable columns
-    "
-    |num|
-
-    num := 0.
-    self columnsDo:[:aCol| aCol canSelect ifTrue:[num := num + 1] ].
-    ^ num
-!
-
 rowHeight
     "get the height of the highest row in pixels
     "
@@ -1166,7 +1355,7 @@
     "returns vertical/horizontal size of a separator dependent on the
      3D effect.
     "
-    ^ has3Dsepartors ifTrue:[4] ifFalse:[1]
+    ^ separatorSize
 
 !
 
@@ -1194,10 +1383,10 @@
         rowHeight := (aCol heightOfHighestRow) max:rowHeight.
         x := x + (aCol minWidth).
     ].
-    rowHeight := rowHeight + (2 * verticalSpacing) + (self separatorSize).
+    rowHeight := rowHeight + separatorSize + verticalSpacing + verticalSpacing.
     preferredExtent := (x + margin + margin) @ (self numberOfRows * rowHeight).
 
-    x := (rowHeight - font height) // 2 + font ascent.
+    x := (rowHeight - separatorSize - font height) // 2 + font ascent.
     self columnsDo:[:aCol|aCol textInsetChanged:x].
   ^ preferredExtent
 
@@ -1276,7 +1465,7 @@
             y >= height ifTrue:[^ self].
         ].
         aColNr ~~ 0 ifTrue:[                                    "/ redraw column in row
-            w := (self columnAt:aColNr) width - 1.
+            w := (self columnAt:aColNr) width.
 
             (x := self xVisibleOfColNr:aColNr) < margin ifTrue:[
                 (w := w + x) <= margin ifTrue:[
@@ -1298,55 +1487,71 @@
 redrawX:x y:y width:w height:h
     "redraw part of myself immediately, given logical coordinates 
     "
-    |x0 x1 c0 c1 yT xM yTop yBot start stop prevTrans transPoint prevClipArea clipHeight|
+    |c0 c1 prevTrans prevClipArea clipHeight
+     start "{ Class:SmallInteger }"
+     stop  "{ Class:SmallInteger }"
+     x0    "{ Class:SmallInteger }"
+     x1    "{ Class:SmallInteger }"
+     yT    "{ Class:SmallInteger }"
+     xM    "{ Class:SmallInteger }"
+     yTop  "{ Class:SmallInteger }"
+     yBot  "{ Class:SmallInteger }"
+     m2    "{ Class:SmallInteger }"
+     wMinM "{ Class:SmallInteger }"
+    |
 
     shown ifFalse:[^ self].
-
     self paint:bgColor.
     self fillRectangleX:x y:y width:w height:h.
 
-    yT := margin - viewOrigin y.
-    c0 := y - yT.
-
+    columnDescriptors size == 0 ifTrue:[
+        ^ self
+    ].
+    yT    := margin - viewOrigin y.
+    c0    := y - yT.
     start := (c0 // rowHeight) + 1.
-    stop  := (c0 + h - 1 // rowHeight + 1) min:(self numberOfRows).
+    stop  := (c0 + h - 1 // rowHeight + 1) min:(list size).
 
     stop < start ifTrue:[
         ^ self
     ].
-    xM             := (x + w) min:(width - margin).
+    m2             := margin + margin.
+    wMinM          := width  - margin.
+    xM             := (x + w) min:wMinM.
     prevTrans      := transformation.
     prevClipArea   := clipRect.
     clipRect       := nil.
     transformation := WindowingTransformation new.
-    clipHeight     := height - margin - margin.
-    transPoint     := Point x:0 y:yT.
+    clipHeight     := height - m2.
 
     x0    := margin - (viewOrigin x).
     yTop  := (start - 1) * rowHeight.
     yBot  := stop * rowHeight.
 
-    self columnsDo:[:aCol|
-        ((x1 := x0 + aCol width) >= x and:[x0 < xM]) ifTrue:[
+    columnDescriptors do:[:aCol|
+        ((x1 := x0 + aCol width) > x and:[x0 < xM]) ifTrue:[
             c0 := x0 max:margin.
-            c1 := (x1 + 1) min:xM.
+            c1 := x1 - c0.
 
-            device setClipX:c0 y:margin width:(c1 - c0) height:clipHeight
+            x1 < xM ifFalse:[
+                (c0 + c1) > wMinM ifTrue:[
+                    c1 := wMinM - c0
+                ]
+            ].
+            device setClipX:c0 y:margin width:c1 height:clipHeight
                          in:drawableId gc:gcId.
 
-            transPoint x:x0.
-            transformation translation:transPoint.
+            transformation translation:(x0 @ yT ).
             aCol drawFrom:start to:stop yTop:yTop yBot:yBot with:fgColor and:bgColor.
         ].
         x0 := x1
     ].
     transformation := prevTrans.
     clipRect := nil.
-
     prevClipArea isNil ifTrue:[device noClipIn:drawableId  gc:gcId]
                       ifFalse:[self clippingRectangle:prevClipArea].
 
-    (w >= (width - margin - margin) and:[h >= (height - margin - margin)]) ifTrue:[
+    (h >= clipHeight and:[w >= (width - m2)]) ifTrue:[
         self sensor flushExposeEventsFor:self.
     ].
 ! !
@@ -1562,26 +1767,71 @@
 scrollToSelection
     "make selection visible
     "
-    self hasSelection ifTrue:[
-        self scrollToRowAt:selectedRowIndex colAt:selectedColIndex
+    |rowNr|
+
+    (rowNr := self firstIndexSelected) ~~ 0 ifTrue:[
+        self scrollToRowAt:rowNr colAt:(self selectedColIndex)
     ]
 
 ! !
 
 !DSVColumnView methodsFor:'selection'!
 
+deselect
+    "deselect
+    "
+    self selectColIndex:0 rowIndex:0
+!
+
+firstIndexSelected
+    "returns index of first element selected or 0
+    "
+    multipleSelectOk ifFalse:[
+        ^ selectedRowIndex
+    ].
+    selectedRowIndex size ~~ 0 ifTrue:[
+        ^ selectedRowIndex at:1
+    ].
+    ^ 0
+!
+
 hasSelection
-    "returns true if a selection (raw and column) exists
+    "returns true if a selection exists
     "
-    ^ selectedRowIndex ~~ 0
+    ^ self numberOfSelections ~~ 0
 
 
 !
 
-selectColIndex:aColNr
-    "select new column; keep row index
+isInSelection:aRowNr
+    "return true, if row, aRowNr is in the selection
     "
-    self selectColIndex:aColNr rowIndex:selectedRowIndex
+    aRowNr ~~ 0 ifTrue:[
+        multipleSelectOk ifFalse:[
+            ^ aRowNr == selectedRowIndex
+        ].
+        selectedRowIndex size ~~ 0 ifTrue:[
+            ^ selectedRowIndex includes:aRowNr
+        ]
+    ].
+    ^ false
+!
+
+isSelected:aRowNr inColumn:aColNr
+
+    (self isInSelection:aRowNr) ifTrue:[
+        ^ (selectedColIndex == 0 or:[selectedColIndex == aColNr])
+    ].
+    ^ false
+!
+
+numberOfSelections
+    "return the number of selected rows
+    "
+    multipleSelectOk ifFalse:[
+        ^ selectedRowIndex ~~ 0 ifTrue:[1] ifFalse:[0]
+    ].
+    ^ selectedRowIndex size
 !
 
 selectColIndex:aColNr rowIndex:aRowNr
@@ -1589,33 +1839,28 @@
     "
     |oC oR|
 
-    oC := selectedColIndex.
-    oR := selectedRowIndex.
+    oC := self selectedColIndex.
+    oR := self selectedRowIndex.
 
     self setSelectColIndex:aColNr rowIndex:aRowNr.
 
-    (oC ~~ selectedColIndex or:[oR ~~ selectedRowIndex]) ifTrue:[
+    (oC ~~ self selectedColIndex or:[oR ~= self selectedRowIndex]) ifTrue:[
         self selectionChanged
     ].
 !
 
-selectRow:aRow
+selectRow:something
     "select a row
     "
-    |rowNr|
-
-    (aRow notNil and:[list size ~~ 0]) ifTrue:[
-        rowNr := list identityIndexOf:aRow
-    ] ifFalse:[
-        rowNr := 0
-    ].
-    self selectRowIndex:rowNr.
+    ^ self selectedRowIndex:something
 !
 
-selectRowIndex:aRowNr
-    "select new row; keep column index
+selectRowIndex:something
+    "set selection of rows
     "
-    self selectColIndex:selectedColIndex rowIndex:aRowNr
+    self selectColIndex:selectedColIndex rowIndex:something
+
+
 !
 
 selectedColIndex
@@ -1631,9 +1876,22 @@
 !
 
 selectedRow
-    "returns selected row or nil
+    "returns selected row (or collection if multiple selection) or nil
     "
-    ^ self at:selectedRowIndex ifAbsent:nil
+    multipleSelectOk ifFalse:[
+        ^ self at:selectedRowIndex ifAbsent:nil
+    ].
+
+    selectedRowIndex size ~~ 0 ifTrue:[
+        ^ selectedRowIndex collect:[:i| self at:i]
+    ].
+    ^ nil
+!
+
+selectedRow:something
+    "select something
+    "
+    self selectedRowIndex:something
 !
 
 selectedRowIndex
@@ -1642,13 +1900,12 @@
     ^ selectedRowIndex
 !
 
-selectedRowIndexInColumn:aCol
-    selectedRowIndex ~~ 0 ifTrue:[
-        (selectedColIndex == 0 or:[self selectedColumn == aCol]) ifTrue:[
-            ^ selectedRowIndex
-        ]
-    ].
-    ^ 0
+selectedRowIndex:something
+    "set selection of rows
+    "
+    self selectColIndex:selectedColIndex rowIndex:something
+
+
 !
 
 selectionChanged
@@ -1657,56 +1914,89 @@
     self changed:#selection.
 
     actionBlock notNil ifTrue:[
-        actionBlock value:selectedRowIndex
+        actionBlock value:(self selectedRowIndex)
+    ]
+!
+
+selectionIndicesDo:aOneArgBlock
+    "evaluate block on each row selected; the argument to the row
+     is the index of the selected row
+    "
+    multipleSelectOk ifFalse:[
+        selectedRowIndex ~~ 0 ifTrue:[
+            aOneArgBlock value:selectedRowIndex
+        ]
+    ] ifTrue:[
+        selectedRowIndex size ~~ 0 ifTrue:[
+            selectedRowIndex do:[:i| aOneArgBlock value:i ]
+        ]
     ]
 !
 
 setSelectColIndex:aColNr rowIndex:aRowNr
     "change selection without notification
     "
-    |rowNr colNr newCol oldCol oldRow level sensor|
+    |rowNr colNr newCol oldCol oldRow sensor sglSelRow sz|
 
-    (aRowNr between:0 and:(self numberOfRows)) ifTrue:[rowNr := aRowNr]
-                                              ifFalse:[rowNr := 0].
-
-    colNr := 0.
+    rowNr := self validateSelection:aRowNr.
 
-    (     rowNr ~~ 0
-     and:[(aColNr between:1 and:(self numberOfColumns))
-     and:[(self columnAt:aColNr) rendererType ~~ #rowSelector]]
-    ) ifTrue:[
-        newCol := self columnAt:aColNr.
-
-        newCol canSelect ifTrue:[colNr  := aColNr]
-                        ifFalse:[newCol := nil]
-        
+    multipleSelectOk ifTrue:[
+        colNr := (rowNr size == 1) ifTrue:[aColNr] ifFalse:[0]
+    ] ifFalse:[
+        colNr := rowNr ~~ 0 ifTrue:[aColNr] ifFalse:[0]
     ].
 
-    (rowNr == selectedRowIndex and:[colNr == selectedColIndex]) ifTrue:[
+    (colNr := colNr ? 0) ~~ 0 ifTrue:[
+        newCol := self columnAt:colNr.
+        newCol rendererType == #rowSelector ifTrue:[
+            colNr := 0.
+            newCol := nil
+        ] ifFalse:[
+            multipleSelectOk ifTrue:[sglSelRow := rowNr at:1]
+                            ifFalse:[sglSelRow := rowNr].
+
+            (newCol canSelect:sglSelRow) ifFalse:[
+                newCol := nil.
+                colNr  := 0
+            ]
+        ]
+    ].
+
+    (rowNr = selectedRowIndex and:[colNr == selectedColIndex]) ifTrue:[
         ^ self  "/ nothing changed
     ].
 
     "/ release old selection
 
+    sz := self numberOfSelections.
+
     oldCol := selectedColIndex.
     oldRow := selectedRowIndex.
     selectedRowIndex := rowNr.
     selectedColIndex := colNr.
 
-    oldRow ~~ 0 ifTrue:[
-        editValue notNil ifTrue:[
-            (self columnAt:oldCol) at:oldRow put:editValue value.
-            editValue := nil
-        ].
+    sz ~~ 0 ifTrue:[
+        sz > 1 ifTrue:[
+            self realized ifTrue:[                              "/ clear selection
+                oldRow do:[:i|self redrawRowAt:i colAt:0]
+            ]
+        ] ifFalse:[
+            multipleSelectOk ifTrue:[oldRow := oldRow at:1].
 
-        editView notNil ifTrue:[
-            editView destroy.
-            editView := nil.
-        ].
-        "/ redraw old selection unselected
-        self realized ifTrue:[
-            self redrawRowAt:oldRow colAt:oldCol.
-        ]        
+            editValue notNil ifTrue:[                           "/ set value to row
+                (self columnAt:oldCol) at:oldRow put:editValue value.
+                editValue := nil
+            ].
+
+            editView notNil ifTrue:[
+                editView destroy.
+                editView := nil.                                "/ get expose event
+            ] ifFalse:[
+                self realized ifTrue:[                          "/ have to redraw
+                    self redrawRowAt:oldRow colAt:oldCol.
+                ]
+            ]        
+        ]
     ].   
 
     "/ show new selection
@@ -1714,41 +2004,75 @@
     self realized ifFalse:[^ self ].
 
     newCol notNil ifTrue:[
-        self scrollToRowAt:rowNr colAt:colNr.
+        self scrollToRowAt:sglSelRow colAt:colNr.
 
         newCol editorType ~~ #None ifTrue:[
-
-            level := 1 + self separatorSize.
-            editView := SimpleView extent:((newCol width - level) @ (rowHeight - level)) in:self.
+            editView := SimpleView extent:(  (newCol width - separatorSize) 
+                                           @ (rowHeight    - separatorSize)
+                                          )
+                                       in:self.
             self updateEditViewOrigin.
             editView viewBackground:hgLgBgColor.
 
-            editValue := newCol editorForRow:(self at:rowNr)
+            editValue := newCol editorForRow:(self at:sglSelRow)
                                           in:editView
                                         with:hgLgFgColor
                                           bg:hgLgBgColor.
             editView realize.
         ] ifFalse:[
-            self redrawRowAt:rowNr colAt:colNr
+            self redrawRowAt:sglSelRow colAt:colNr
         ]
     ] ifFalse:[
-        selectedRowIndex ~~ 0 ifTrue:[
-            self redrawRowAt:rowNr colAt:0.
-            self scrollToRowAt:rowNr colAt:0.
+        (sz := self firstIndexSelected) ~~ 0 ifTrue:[   "/ redraw new selection
+            self selectionIndicesDo:[:i| self redrawRowAt:i colAt:0 ].
+            self scrollToRowAt:sz colAt:0.
         ]
     ].
 
-    (sensor := self sensor) notNil ifTrue:[
+    (sensor := self sensor) notNil ifTrue:[             "/ catch expose events
         [sensor hasExposeEventFor:nil] whileTrue:[
             self windowGroup processExposeEvents
         ]
     ]
 
 
+!
+
+validateSelection:aSelection
+    |newSel|
+
+    newSel := aSelection.
+
+    (list size == 0 or:[newSel isNil or:[newSel == 0]]) ifTrue:[
+        ^ multipleSelectOk ifFalse:[0] ifTrue:[nil]
+    ].
+
+    newSel isNumber ifTrue:[
+        ^ multipleSelectOk ifFalse:[newSel] ifTrue:[OrderedCollection with:newSel]
+    ].
+    multipleSelectOk ifFalse:[
+        newSel := list identityIndexOf:aSelection
+    ] ifTrue:[
+        newSel := nil.
+
+        aSelection size ~~ 0 ifTrue:[
+            aSelection first isNumber ifTrue:[
+                newSel := aSelection
+            ] ifFalse:[
+                aSelection do:[:el||n|
+                    (n := list identityIndexOf:el) ~~ 0 ifTrue:[
+                        newSel isNil ifTrue:[newSel := OrderedCollection new].
+                        newSel add:n
+                    ]
+                ]
+            ]
+        ]
+    ].
+    ^ newSel
 ! !
 
 !DSVColumnView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/DSVColumnView.st,v 1.9 1997-10-31 10:25:05 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/DSVColumnView.st,v 1.10 1997-11-07 13:27:22 ca Exp $'
 ! !
--- a/DSVLabelView.st	Mon Nov 03 16:19:36 1997 +0100
+++ b/DSVLabelView.st	Fri Nov 07 14:27:53 1997 +0100
@@ -199,8 +199,11 @@
 redrawX:x y:y width:w height:h
     "redraw an area
     "
-    |x0 x1 xM prevTransform prevClipArea fg bg bgLbl fgLbl textY hSpace dkCol lgCol has3D|
-
+    |prevTransform prevClipArea fg bg bgLbl textY hSpace dkCol lgCol has3D
+     x0 "{ Class:SmallInteger }"
+     x1 "{ Class:SmallInteger }"
+     xM "{ Class:SmallInteger }"
+    |
     self shown ifFalse:[
         ^ self
     ].
@@ -212,7 +215,7 @@
     hSpace := columnView horizontalSpacing.
 
     self paint:bg.
-    self fillRectangleX:x y:y width:w height:(h min:height).
+    self fillRectangleX:x y:y width:w height:height.
     columnView numberOfColumns == 0 ifTrue:[
         ^ self
     ].
@@ -222,26 +225,21 @@
     clipRect       := nil.
     transformation := WindowingTransformation new.
 
-    has3D := columnView has3Dsepartors.
+    has3D := columnView has3Dseparators.
     dkCol := columnView separatorDarkColor.
     lgCol := columnView separatorLightColor.
 
     self paint:fg on:bg.
 
     columnView columnsDo:[:aCol||label c1 c2|
-        x1 := x0 + aCol width.
-
-        (x1 >= x and:[x0 <= xM]) ifTrue:[
+        ((x1 := x0 + aCol width) > x and:[x0 < xM]) ifTrue:[
             c1 := x0 max:0.
             c2 := x1 min:(width - 1).
 
-            device setClipX:c1 y:0 width:(c2 - c1 + 1) height:height
+            device setClipX:c1 y:0 width:(c2 - c1) height:height
                          in:drawableId gc:gcId.
 
-            bgLbl := aCol backgroundColor.
-            fgLbl := aCol foregroundColor.
-
-            bgLbl notNil ifTrue:[
+            (bgLbl := aCol backgroundColor) notNil ifTrue:[
                 self paint:bgLbl.
                 self fillRectangleX:x0 y:0 width:(aCol width) height:height.
             ] ifFalse:[
@@ -250,17 +248,11 @@
          "/ draw label
 
             (label := aCol label) notNil ifTrue:[                
+                self paint:(aCol foregroundColor ? fg) on:bgLbl.
+
                 label isString ifTrue:[
-                    aCol canSelect ifTrue:[
-                        fgLbl isNil ifTrue:[fgLbl := fg]
-                    ] ifFalse:[
-                        fgLbl isNil ifTrue:[fgLbl := dkCol]
-                    ].
-                    self paint:fgLbl on:bg.
                     label displayOn:self x:x0 + hSpace y:textY
                 ] ifFalse:[
-                    fgLbl isNil ifTrue:[fgLbl := fg].
-                    self paint:fgLbl on:bg.
                     label displayOn:self x:x0 + hSpace y:((height - (label heightOn:self)) // 2)
                 ].
             ].
@@ -270,19 +262,21 @@
              and:[aCol ~~ columnView lastColumn
               or:[columnView canFit not]]
             ) ifTrue:[
-            "/ aCol showColSeparator ifTrue:[
+                x1 := x1 - 1.
+
                 has3D ifFalse:[
                     self paint:fg.                                              "/ no 3D-Effect
                     self displayLineFromX:x1     y:0 toX:x1     y:height
                 ] ifTrue:[                                                      "/ with 3D-Effect
-                    self paint:dkCol.
+                    self paint:lgCol.
                     self displayLineFromX:x1     y:0 toX:x1     y:height.
                     self displayLineFromX:x1 - 1 y:0 toX:x1 - 1 y:height.
 
-                    self paint:lgCol.
+                    self paint:dkCol.
                     self displayLineFromX:x1 - 2 y:0 toX:x1 - 2 y:height.
                     self displayLineFromX:x1 - 3 y:0 toX:x1 - 3 y:height.
-                ]
+                ].
+                x1 := x1 + 1.
             ]
         ].
         x0 := x1.
@@ -293,7 +287,7 @@
     prevClipArea isNil ifTrue:[device noClipIn:drawableId  gc:gcId]
                       ifFalse:[self clippingRectangle:prevClipArea].
 
-    has3D ifTrue:[self paint:lgCol]
+    has3D ifTrue:[self paint:dkCol]
          ifFalse:[self paint:fg].
 
     self displayLineFromX:0 y:(height - 1) toX:x1 y:(height - 1).
@@ -332,5 +326,5 @@
 !DSVLabelView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/DSVLabelView.st,v 1.5 1997-11-03 13:13:38 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/DSVLabelView.st,v 1.6 1997-11-07 13:27:37 ca Exp $'
 ! !
--- a/DataSetColumn.st	Mon Nov 03 16:19:36 1997 +0100
+++ b/DataSetColumn.st	Fri Nov 07 14:27:53 1997 +0100
@@ -14,10 +14,10 @@
 
 
 Object subclass:#DataSetColumn
-	instanceVariableNames:'dataSet label minWidth width description form form2 formInset
-		textInset writeSelector drawableAction backgroundColor
+	instanceVariableNames:'columnNumber dataSet label minWidth width description form form2
+		formInset textInset writeSelector drawableAction backgroundColor
 		foregroundColor'
-	classVariableNames:'FormComboView FormToggleOn FormToggleOff FormRowSelector'
+	classVariableNames:''
 	poolDictionaries:''
 	category:'Views-DataSet'
 !
@@ -70,99 +70,6 @@
 
 ! !
 
-!DataSetColumn class methodsFor:'instance creation'!
-
-on:aDSVColumnView description:aDescription
-    "instance creation
-    "
-    ^ self new on:aDSVColumnView description:aDescription
-
-! !
-
-!DataSetColumn class methodsFor:'constants'!
-
-formComboView
-    "returns combo form (used by #ComboList #ComboBox)
-    "
-    FormComboView isNil ifTrue:[
-        FormComboView := Image fromFile:'dsv_comboList.xpm'.
-    ].
-    ^ FormComboView
-
-"
-FormComboView := nil
-"
-
-
-
-
-!
-
-formRowSelector
-    "returns form used by rowSelector
-    "
-    FormRowSelector notNil ifTrue:[
-        ^ FormRowSelector
-    ].
-
-    FormRowSelector := Form
-                  width:8
-                 height:11
-              fromArray:#[2r01000000
-                          2r01100000
-                          2r01110000
-                          2r01111000
-                          2r01111100
-                          2r01111110
-                          2r01111100
-                          2r01111000
-                          2r01110000
-                          2r01100000
-                          2r01000000]
-                     on:Display.
-
-    FormRowSelector := FormRowSelector asImage.
-    ^ FormRowSelector.
-
-"
-FormRowSelector := nil
-"
-
-
-!
-
-formToggleOff
-    "returns toggle-OFF form (used by #CheckToggle value:false)
-    "
-    FormToggleOff isNil ifTrue:[
-        FormToggleOff := Image fromFile:'dsv_checkTgOff.xpm'.
-    ].
-    ^ FormToggleOff.
-
-"
-FormToggleOff := nil
-"
-
-
-!
-
-formToggleOn
-    "returns toggle-ON form (used by #CheckToggle value:true )
-    "
-    FormToggleOn isNil ifTrue:[
-        FormToggleOn := Image fromFile:'dsv_checkTgOn.xpm'.
-    ].
-    ^ FormToggleOn.
-
-"
-FormToggleOn := nil
-"
-
-
-
-
-! !
-
 !DataSetColumn methodsFor:'accessing'!
 
 at:aRowNr
@@ -204,37 +111,36 @@
 
     (    (width := description width)    ~~ 0                   "/ fixed size
      or:[(width := description minWidth) ~~ 0]                  "/ start size
-    ) ifTrue:[
-        ^ minWidth := width
-    ].
-    drawableAction notNil ifTrue:[
-        "/ take maximum 10 entries to calculate the width;
-        "/ can be resized later if neccessary
+    ) ifFalse:[
+        drawableAction notNil ifTrue:[
+            "/ take maximum 10 entries to calculate the width;
+            "/ can be resized later if neccessary
 
-        end := 10 min:dataSet numberOfRows.
+            end := 10 min:dataSet numberOfRows.
 
-        1 to:end do:[:aRowNr||lbl|
-            lbl := drawableAction value:aRowNr.
+            1 to:end do:[:aRowNr||lbl|
+                lbl := drawableAction value:aRowNr.
 
-            (lbl respondsTo:#widthOn:) ifTrue:[
-                width := width max:(lbl widthOn:dataSet)
-            ] ifFalse:[
-                lbl notNil ifTrue:[
-                    width := width max:(lbl displayString widthOn:dataSet)
+                (lbl respondsTo:#widthOn:) ifTrue:[
+                    width := width max:(lbl widthOn:dataSet)
+                ] ifFalse:[
+                    lbl notNil ifTrue:[
+                        width := width max:(lbl displayString widthOn:dataSet)
+                    ]
                 ]
+            ].
+            description editorType ~~ #None ifTrue:[
+                width := width + (dataSet font widthOn:dataSet device)
+            ].
+            form notNil ifTrue:[
+                width := width + form width
             ]
+        ] ifFalse:[
+            width := width + form2 width
         ].
-        description editorType ~~ #None ifTrue:[
-            width := width + (dataSet font widthOn:dataSet device)
+        label notNil ifTrue:[
+            width := width max:(label widthOn:dataSet)
         ].
-        form notNil ifTrue:[
-            width := width + form width
-        ]
-    ] ifFalse:[
-        width := width + form2 width
-    ].
-    label notNil ifTrue:[
-        width := width max:(label widthOn:dataSet)
     ].
     ^ width := minWidth := width + dataSet separatorSize + (2 * dataSet horizontalSpacing).
 !
@@ -257,61 +163,65 @@
 drawFrom:start to:stop yTop:yTop yBot:yBot with:fgColor and:bgColor
     "redraw rows between start and stop
     "
-    |lgCol dkCol isLast fg bg selRowNr label drawColSep n
+    |lgCol dkCol fg bg val drawColSep n isLast lblFg lblBg
      rowHeight "{ Class:SmallInteger }"
      nTimes    "{ Class:SmallInteger }"
+     sepSize   "{ Class:SmallInteger }"
      y         "{ Class:SmallInteger }"
+     y1        "{ Class:SmallInteger }"
      x         "{ Class:SmallInteger }"
+     w         "{ Class:SmallInteger }"
     |
     rowHeight := dataSet rowHeight.
     nTimes    := stop - start + 1.
+    sepSize   := dataSet separatorSize.
 
     (bg := backgroundColor) isNil ifTrue:[
         bg := bgColor
     ] ifFalse:[
         dataSet paint:bg.
-        dataSet fillRectangleX:0 y:yTop width:width height:(nTimes * rowHeight)
+        dataSet fillRectangleX:0 y:yTop width:width height:(nTimes * rowHeight - 1)
     ].
-
-    fg := foregroundColor ? fgColor.
-    y  := yTop + textInset.
-    x  := dataSet horizontalSpacing.
-    selRowNr := dataSet selectedRowIndexInColumn:self.
+    (fg := foregroundColor) notNil ifTrue:[
+        lgCol := fg
+    ] ifFalse:[
+        fg := fgColor.
+        lgCol := dataSet hgLgFgColor.
+    ].
+    dkCol := dataSet hgLgBgColor.
+    y     := yTop + textInset.
+    x     := dataSet horizontalSpacing.
+    val   := nil.
 
-    (selRowNr between:start and:stop) ifTrue:[
-        n := selRowNr - 1 * rowHeight.
+    start to:stop do:[:i|
+        (dataSet isSelected:i inColumn:columnNumber) ifTrue:[
+            dataSet paint:dkCol.
+            dataSet fillRectangleX:0 y:(y - textInset) width:width height:(rowHeight - 1 - sepSize).
+            lblFg := lgCol.
+            lblBg := dkCol.
 
-        dataSet paint:(lgCol := dataSet hgLgBgColor).
-        dataSet fillRectangleX:1 y:n width:width - 1 height:rowHeight - 1.
-        n := n + textInset.
-        dataSet paint:(dataSet hgLgFgColor) on:lgCol.
-
-        drawableAction notNil ifTrue:[
-            (label := drawableAction value:selRowNr) notNil ifTrue:[
-                label displayOn:dataSet x:x y:n
+            description rendererType == #rowSelector ifTrue:[
+                val := form2
             ]
         ] ifFalse:[
-            description rendererType == #rowSelector ifTrue:[
-                form2 displayOn:dataSet x:x y:n    
-            ]
-        ]
+            lblFg := fg.
+            lblBg := bg.
+        ].        
+        (val notNil or:[drawableAction notNil and:[(val := drawableAction value:i) notNil]]) ifTrue:[
+            val isText ifTrue:[
+                lblFg := self extractForegrounColorFromText:val ifAbsent:lblFg.
+            ].
+            dataSet paint:lblFg on:lblBg.
+            val displayOn:dataSet x:x y:y.
+            val := nil.
+        ].
+        y := y + rowHeight
     ].
     dataSet paint:fg on:bg.
 
-    drawableAction notNil ifTrue:[
-        start to:stop do:[:aRowNr|
-            (     selRowNr ~~ aRowNr
-             and:[(label := drawableAction value:aRowNr) notNil]
-            ) ifTrue:[
-                label displayOn:dataSet x:x y:y
-            ].
-            y := y + rowHeight
-        ]
-    ].
-
     form notNil ifTrue:[
-        y := yTop + formInset.
-        x := width - form width - dataSet separatorSize.
+        y := yTop  + formInset.
+        x := width - form width - sepSize.
 
         form2 isNil ifTrue:[
             nTimes timesRepeat:[
@@ -322,8 +232,8 @@
             x := x // 2.
 
             start to:stop do:[:i|
-                (self at:i) == false ifTrue:[dataSet displayForm:form2 x:x y:y]
-                                    ifFalse:[dataSet displayForm:form  x:x y:y].
+                val := (self at:i) == false ifTrue:[form2] ifFalse:[form].
+                dataSet displayForm:val x:x y:y.
                 y := y + rowHeight.
             ]
         ].
@@ -331,28 +241,21 @@
 
     "/ ************************** DRAW SEPARATORS **************************
 
-    (drawColSep := description showColSeparator) ifTrue:[
-        (isLast := dataSet lastColumn == self) ifTrue:[
-            drawColSep := dataSet canFit not.
-        ]
-    ].
+    drawColSep := description showColSeparator.
+    w          := width - 1.
 
-    dataSet has3Dsepartors ifFalse:[
+    sepSize == 1 ifTrue:[
         dataSet paint:fgColor.
 
         drawColSep ifTrue:[
-            dataSet displayLineFromX:width y:yTop toX:width y:yBot.
+            dataSet displayLineFromX:w y:yTop toX:w y:yBot
         ].
         description showRowSeparator ifTrue:[
-            y := yTop.
-
-            start > 1 ifTrue:[
-                dataSet displayLineFromX:0 y:y toX:width y:y.
-            ].
+            y := yTop - 1.
 
             nTimes timesRepeat:[
                 y := y + rowHeight.
-                dataSet displayLineFromX:0 y:y toX:width y:y.
+                dataSet displayLineFromX:0 y:y toX:w y:y.
             ]
         ].
         ^ self
@@ -363,63 +266,77 @@
     dkCol := dataSet separatorDarkColor.
     lgCol := dataSet separatorLightColor.
 
-    dataSet paint:dkCol.
-
     drawColSep ifTrue:[
-        isLast ifFalse:[
-            dataSet displayLineFromX:width     y:yTop toX:width     y:yBot.
-            dataSet displayLineFromX:width - 1 y:yTop toX:width - 1 y:yBot.
-        ].
         dataSet paint:lgCol.
-        dataSet displayLineFromX:width - 2 y:yTop toX:width - 2 y:yBot.
-        dataSet displayLineFromX:width - 3 y:yTop toX:width - 3 y:yBot.
+        y := yBot - 1. dataSet displayLineFromX:w y:yTop toX:w y:y.
+        w := w    - 1. dataSet displayLineFromX:w y:yTop toX:w y:y.
         dataSet paint:dkCol.
+        y := y - 1.
+        w := w - 1. dataSet displayLineFromX:w y:yTop toX:w y:y.
+        w := w - 1. dataSet displayLineFromX:w y:yTop toX:w y:y.
+        w := width - 1.
+        isLast := dataSet lastColumn == self.
     ].
 
     description showRowSeparator ifTrue:[
-        x := (dataSet firstColumn == self) ifTrue:[0] ifFalse:[1].
-        y := yTop.
-        n := nTimes.
+        drawColSep ifTrue:[
+            n := w - 2
+        ] ifFalse:[
+            n := w.
+        ].
+        dataSet paint:lgCol.
+        y := yTop - 1.
 
-        start ~~ 1 ifTrue:[n := n + 1]
-                  ifFalse:[y := y + rowHeight].
+        nTimes timesRepeat:[
+            y  := y + rowHeight.
+            y1 := y - 1.
+            dataSet displayLineFromX:0 y:y  toX:w y:y.
+            dataSet displayLineFromX:0 y:y1 toX:w y:y1.
+        ].
 
-        drawColSep ifTrue:[
-            n timesRepeat:[
-                dataSet displayLineFromX:x y:y     toX:width-4 y:y.
-                dataSet displayLineFromX:x y:y - 1 toX:width-3 y:y - 1.
+        dataSet paint:dkCol.
+        y := yTop.
+
+        nTimes timesRepeat:[
+            y  := y + rowHeight.
+            y1 := y - 4. dataSet displayLineFromX:0 y:y1 toX:n y:y1.
+            y1 := y - 3. dataSet displayLineFromX:0 y:y1 toX:n y:y1.
 
-                dataSet paint:lgCol.
-                dataSet displayLineFromX:0 y:y - 2 toX:width     y:y - 2.
-                dataSet displayLineFromX:0 y:y - 3 toX:width - 2 y:y - 3.
-                dataSet paint:dkCol.
-                y := y + rowHeight.
+            drawColSep ifTrue:[
+                dataSet displayPointX:n y:y - 1.
+                isLast ifFalse:[
+                    dataSet displayPointX:w y:y1
+                ]
             ]
+        ].
+
+        dataSet size == stop ifTrue:[
+            dataSet paint:lgCol.
+            dataSet displayPointX:n y:y - 1.
+        ]
+    ]
+
+!
+
+extractForegrounColorFromText:aText ifAbsent:aDefColor
+    "extract foreground color from a text object; if no color
+     detected, the default color is returned.
+    "
+    |run color|
+
+    run := aText emphasis.
+
+    run size == 0 ifFalse:[
+        run := run first.
+
+        run size == 0 ifTrue:[
+            (color := run value) isColor ifTrue:[^ color]
         ] ifFalse:[
-            n timesRepeat:[
-                dataSet displayLineFromX:x y:y     toX:width y:y.
-                dataSet displayLineFromX:x y:y - 1 toX:width y:y - 1.
-
-                dataSet paint:lgCol.
-                dataSet displayLineFromX:0 y:y - 2 toX:width y:y - 2.
-                dataSet displayLineFromX:0 y:y - 3 toX:width y:y - 3.
-                dataSet paint:dkCol.
-                y := y + rowHeight.
-            ]
+            run do:[:r| (color := r value) isColor ifTrue:[^ color]]
         ]
     ].
-
-    (drawColSep and:[isLast]) ifTrue:[
-        dataSet displayLineFromX:width     y:yTop toX:width     y:yBot.
-        dataSet displayLineFromX:width - 1 y:yTop toX:width - 1 y:yBot.
-    ].
+  ^ aDefColor
 
-    stop == dataSet size ifTrue:[
-        description showRowSeparator ifTrue:[
-            dataSet displayLineFromX:0 y:yBot     toX:width y:yBot.
-            dataSet displayLineFromX:0 y:yBot - 1 toX:width y:yBot - 1.
-        ]
-    ].
 !
 
 invalidate
@@ -443,7 +360,7 @@
 textInsetChanged:aTextInset
     "recompute all attributes
     "
-    |lbl|
+    |lbl img|
 
     drawableAction notNil ifTrue:[
         textInset := dataSet verticalSpacing.
@@ -458,21 +375,20 @@
                     textInset := aTextInset.
                 ]
             ]
-        ].
+        ]
+    ].
 
-        form notNil ifTrue:[
-            formInset := (   dataSet rowHeight 
-                           - form height 
-                           - dataSet separatorSize
-                         ) // 2 + 1
-        ] ifFalse:[
-            formInset := 0
-        ]
-    ] ifFalse:[
-        formInset := textInset := (   dataSet rowHeight 
-                                    - form2 height 
-                                    - dataSet separatorSize
-                                  ) // 2 + 1.
+    (img := form2 ? form) isNil ifTrue:[
+        formInset := 0
+    ] ifFalse:[        
+        formInset := ( (dataSet rowHeight)
+                      - img height
+                      - (dataSet separatorSize)
+                     ) // 2.
+
+        drawableAction isNil ifTrue:[
+            textInset := formInset
+        ]        
     ].
 
 
@@ -510,11 +426,12 @@
 
 !DataSetColumn methodsFor:'initialization'!
 
-on:aDSVColumnView description:aDescription
+on:aDSVColumnView description:aDescription columnNumber:aNumber
     "instance creation; set attributes dependent on the description
     "
     |rendererType device selector formatStr idx|
 
+    columnNumber    := aNumber.
     dataSet         := aDSVColumnView.
     description     := aDescription.
     rendererType    := description rendererType.
@@ -538,21 +455,18 @@
     ].
 
     rendererType == #CheckToggle ifTrue:[
-        form       := self class formToggleOn  onDevice:device.
-        form2      := self class formToggleOff onDevice:device.
-        form clearMaskedPixels.
-        form2 clearMaskedPixels.
+        form  := dataSet toggleOnButton.
+        form2 := dataSet toggleOffButton.
         ^ self
     ].
 
     rendererType == #rowSelector ifTrue:[
-        form2 := self class formRowSelector onDevice:device.
+        form2 := dataSet rowSelectorButton.
         ^ self
     ].
 
     (rendererType == #ComboBox or:[rendererType == #ComboList]) ifTrue:[
-        form := self class formComboView onDevice:device.
-        form clearMaskedPixels.
+        form := dataSet comboViewButton.
     ].
 
     selector := description printSelector.
@@ -613,6 +527,18 @@
 
 !DataSetColumn methodsFor:'queries'!
 
+canSelect:aRowNr
+    "returns true if cell in column is selectable
+    "
+    |s|
+
+    description canSelect ifTrue:[
+        ^ ((s := description selectSelector) isNil or:[(dataSet at:aRowNr) perform:s])
+    ].
+    ^ false
+
+!
+
 heightOfHighestRow
     "returns the height of the highest row in pixels
     "
@@ -675,5 +601,5 @@
 !DataSetColumn class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/DataSetColumn.st,v 1.8 1997-11-03 13:14:14 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/DataSetColumn.st,v 1.9 1997-11-07 13:27:44 ca Exp $'
 ! !
--- a/DataSetView.st	Mon Nov 03 16:19:36 1997 +0100
+++ b/DataSetView.st	Fri Nov 07 14:27:53 1997 +0100
@@ -89,7 +89,7 @@
     clDc last choices:#choices.
     clDc add:( DataSetColumnSpec label:'Toggle' editorType:#CheckToggle selector:#toggle ).
 
-    scr has3Dsepartors:true.
+    scr has3Dseparators:true.
     scr columnDescriptors:clDc.
     scr list:rows.
     top open.
@@ -131,7 +131,7 @@
     clDc last choices:#choices.
     clDc add:( DataSetColumnSpec label:'Toggle' editorType:#CheckToggle selector:#toggle ).
 
-    scr has3Dsepartors:true.
+    scr has3Dseparators:true.
     scr columnDescriptors:clDc.
     scr list:rows.
     top open.
@@ -161,7 +161,7 @@
 
     scr columnDescriptors:clDc.
     scr beDependentOfRows:false.
-    scr has3Dsepartors:false.
+    scr has3Dseparators:false.
 
     top openAndWait.
     tmArr := Array new:4.
@@ -237,7 +237,7 @@
     clDc last choices:#choices.
     clDc add:( DataSetColumnSpec label:'Toggle' editorType:#CheckToggle selector:#toggle ).
 
-    scr has3Dsepartors:true.
+    scr has3Dseparators:true.
     scr columnDescriptors:clDc.
     scr list:rows.
     top open.
@@ -248,7 +248,9 @@
 "
 !
 
-test
+test:with3Dseparators
+    "performance test
+    "
     |t1 top scr clDc rows slct list bool tmArr listModel|
 
     top  := StandardSystemView new label:'select'; extent:600@440.
@@ -268,7 +270,7 @@
 
     scr columnDescriptors:clDc.
     scr beDependentOfRows:false.
-    scr has3Dsepartors:false.
+    scr has3Dseparators:with3Dseparators.
 
     top openAndWait.
     tmArr := Array new:8.
@@ -453,11 +455,7 @@
             ].
             model == listHolder ifFalse:[
                 what == #value ifTrue:[
-                    (val := model value) isNumber ifTrue:[
-                        columnView selectRowIndex:val
-                    ] ifFalse:[
-                        columnView selectRow:val
-                    ]
+                    columnView selectRowIndex:model value
                 ].
                 ^ self
             ].
@@ -618,5 +616,5 @@
 !DataSetView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/DataSetView.st,v 1.3 1997-10-22 13:26:57 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/DataSetView.st,v 1.4 1997-11-07 13:27:53 ca Exp $'
 ! !