refactored;
authorClaus Gittinger <cg@exept.de>
Fri, 25 Jul 2008 14:43:47 +0200
changeset 3504 7a480e6164ea
parent 3503 f14e20004081
child 3505 f5964848f894
refactored; added RadioButton style
DSVColumnView.st
--- a/DSVColumnView.st	Thu Jul 24 16:29:21 2008 +0200
+++ b/DSVColumnView.st	Fri Jul 25 14:43:47 2008 +0200
@@ -23,9 +23,10 @@
 		buttonLightColor buttonShadowColor buttonHalfLightColor
 		buttonHalfShadowColor checkToggleExtent checkToggleForm
 		checkToggleActiveImage checkTogglePassiveImage checkToggleLevel
-		comboButtonExtent comboButtonForm comboButtonLevel dropSource
-		columnAdaptor tabAtEndAction tabAtStartAction modifiedChannel
-		autoScroll autoScrollBlock needFitColumns scrollWhenUpdating
+		radioButtonActiveImage radioButtonPassiveImage comboButtonExtent
+		comboButtonForm comboButtonLevel dropSource columnAdaptor
+		tabAtEndAction tabAtStartAction modifiedChannel autoScroll
+		autoScrollBlock needFitColumns scrollWhenUpdating
 		separatorOneDColor selectionForegroundColor
 		selectionForegroundColorNoFocus selectionBackgroundColor
 		selectionBackgroundColorNoFocus previousExtent
@@ -36,9 +37,10 @@
 		ButtonLightColor ButtonShadowColor CheckToggleActiveImage
 		CheckTogglePassiveImage ButtonHalfLightColor
 		ButtonHalfShadowColor ButtonEdgeStyle CheckToggleForm
-		CheckToggleLevel CheckToggleExtent ComboButtonForm
+		CheckToggleLevel CheckToggleExtent RadioButtonForm
+		RadioButtonLevel RadioButtonExtent ComboButtonForm
 		ComboButtonLevel ComboButtonExtent StopRedrawSignal
-		DragMotionDistance'
+		DragMotionDistance RadioButtonActiveImage RadioButtonPassiveImage'
 	poolDictionaries:''
 	category:'Views-DataSet'
 !
@@ -186,6 +188,8 @@
                        #'button.edgeStyle'
                        #'checkToggle.activeImage'
                        #'checkToggle.passiveImage'
+                       #'radioButton.activeImage'
+                       #'radioButton.passiveImage'
                        #'selection.hilightForegroundColor'
                        #'selection.hilightBackgroundColor'   )>
 
@@ -203,25 +207,31 @@
     ButtonHalfLightColor   := StyleSheet colorAt:#'button.halfLightColor'.
     ButtonHalfShadowColor  := StyleSheet colorAt:#'button.halfShadowColor'.
     ButtonEdgeStyle        := StyleSheet at:#'button.edgeStyle'.
+
     CheckToggleActiveImage := StyleSheet at:#'checkToggle.activeImage'.
-
     CheckToggleActiveImage isNil ifTrue:[
         CheckTogglePassiveImage := nil
     ] ifFalse:[
         CheckTogglePassiveImage := StyleSheet at:#'checkToggle.passiveImage'.
-
         CheckTogglePassiveImage isNil ifTrue:[
             CheckToggleActiveImage := nil
         ]
     ].
+    CheckToggleForm   := nil.
+    CheckToggleLevel  := nil.
+    CheckToggleExtent := nil.
+
+    RadioButtonActiveImage := StyleSheet at:#'radioButton.activeImage'.
+    RadioButtonPassiveImage := StyleSheet at:#'radioButton.passiveImage'.
+    (RadioButtonActiveImage isNil or:[ RadioButtonPassiveImage isNil ]) ifTrue:[
+        RadioButtonActiveImage := RadioButton roundOnForm.
+        RadioButtonPassiveImage := RadioButton roundOffForm.
+    ].
+
     ComboButtonForm   := nil.
     ComboButtonLevel  := nil.
     ComboButtonExtent := nil.
 
-    CheckToggleForm   := nil.
-    CheckToggleLevel  := nil.
-    CheckToggleExtent := nil.
-
     "
      self updateStyleCache.
     "
@@ -731,8 +741,17 @@
 
 !DSVColumnView methodsFor:'accessing-columns'!
 
-columnAt:anIndex 
+columnAt:anIndex
+    <resource: #obsolete>
+ 
     "returns the column at an index"
+
+    self obsoleteMethodWarning:'use columnDescriptorAt:'.
+    ^ self columnDescriptorAt:anIndex
+!
+
+columnDescriptorAt:anIndex 
+    "returns the columnDescriptor at an index"
     
     ^ columnDescriptors at:anIndex ifAbsent:nil
 !
@@ -849,6 +868,12 @@
     ^ comboButtonLevel
 !
 
+radioButtonExtent
+    "returns the extent of a radio button"
+    
+    ^ radioButtonActiveImage extent
+!
+
 rowSelectorExtent
     "returns the bitmap of a selected row"
     
@@ -1622,8 +1647,21 @@
 
     col := self selectedColumn.
     col at:firstSelectedIndex put:newValue.
+
+    col editorType == #RadioButton ifTrue:[
+        "/ turn off the other column
+
+        1 to:list size do:[:rowNr |
+            rowNr ~~ firstSelectedIndex ifTrue:[
+                (col at:rowNr) ~~ false ifTrue:[
+                    col at:rowNr put:false.
+                    self invalidateRowAt:rowNr colAt:col columnNumber.
+                ].
+            ]
+        ]
+    ].
+
     realValue := col at:firstSelectedIndex.
-
     (realValue ~= newValue) ifTrue:[
         "/ some validation by the row-object; the stored value
         "/ is different from what I think.
@@ -1633,7 +1671,7 @@
         "/ Q: is this CA's paranoia or could this really be done in the at:put: above ???
         (editValueBefore == editValue) ifTrue:[ 
             editValue value:realValue.
-        ]
+        ].
     ].
 
     modifiedChannel notNil ifTrue:[
@@ -1647,7 +1685,7 @@
     (rowNr := selectedRowIndex) isNumber ifFalse:[
         rowNr := rowNr first.
     ].
-    rowsValue := (self columnAt:self selectedColIndex) at:rowNr.
+    rowsValue := (self columnDescriptorAt:self selectedColIndex) at:rowNr.
     (editValue notNil and:[ editValue value ~= rowsValue ]) ifTrue:[
         editValue value:rowsValue withoutNotifying:self.
         editView 
@@ -1785,7 +1823,7 @@
             y >= height ifTrue:[^ self].
         ].
         aColNr ~~ 0 ifTrue:[                                    "/ redraw column in row
-            col := (self columnAt:aColNr).
+            col := (self columnDescriptorAt:aColNr).
             w := col isNil ifTrue:0 ifFalse:[col width].
             x := self xVisibleOfColNr:aColNr.
 
@@ -1838,7 +1876,9 @@
 !
 
 invalidateSelection
-    shown ifTrue:[ |colIndex|
+    |colIndex|
+
+    shown ifTrue:[ 
         colIndex := self selectedColIndex ? 0.
 
         self selectionIndicesDo:[:aRowIndex|
@@ -2032,7 +2072,7 @@
     "Modified: / 05-02-2007 / 09:07:10 / cg"
 !
 
-drawCheckToggleAtX:xTop y:yTop w:rowWidth state:aState
+drawCheckToggleAtX:xLeft y:yTop w:cellWidth state:cellValue
     "draw a check toggle button"
 
     |e form
@@ -2040,27 +2080,31 @@
      x "{ Class:SmallInteger }"
      h "{ Class:SmallInteger }"
      w "{ Class:SmallInteger }"
-    |
+     state|
+
+    state := (cellValue ? false).
+    state isBoolean ifFalse:[ state := false ].
+
     w := checkToggleExtent x.
     h := checkToggleExtent y.
-    y := yTop + (rowHeight - h // 2).
-    x := xTop + (rowWidth  - w // 2).
+    y := yTop + ((rowHeight - h) // 2).
+    x := xLeft + ((cellWidth  - w) // 2).
     h odd ifTrue:[y := y + 1].
 
-    (form := checkToggleActiveImage) isNil ifTrue:[
+    checkToggleActiveImage isNil ifTrue:[
         self paint:bgColor.
         self fillRectangleX:x y:y width:w height:h.
         self drawEdgesAtX:x   y:y width:w height:h level:checkToggleLevel on:self.
 
-        aState isBoolean ifFalse:[^ self].
-
-        aState ifFalse:[
+        state ifFalse:[
             ^ self
         ].
         self paint:fgColor on:bgColor.
         form := checkToggleForm
     ] ifFalse:[
-        aState ifFalse:[form := checkTogglePassiveImage]
+        form := state 
+                    ifTrue:checkToggleActiveImage
+                    ifFalse:checkTogglePassiveImage.
     ].
     e := (checkToggleExtent - form extent) // 2.
     self displayForm:form x:(x + e x) y:(y + e y).
@@ -2073,11 +2117,11 @@
      x "{ Class:SmallInteger }"
      y "{ Class:SmallInteger }"
      h "{ Class:SmallInteger }"
-     w "{ Class:SmallInteger }"
-    |
+     w "{ Class:SmallInteger }"|
+
     w := comboButtonExtent x.
     h := comboButtonExtent y.
-    y := yTop + (rowHeight - h // 2).
+    y := yTop + ((rowHeight - h) // 2).
     x := xTop + (rowWidth  - w - separatorSize - 1).
     e := (comboButtonExtent - comboButtonForm extent) // 2.
 
@@ -2102,12 +2146,36 @@
         halfShadow:buttonHalfShadowColor
         halfLight:buttonHalfLightColor
         style:ButtonEdgeStyle.
+!
+
+drawRadioButtonAtX:xLeft y:yTop w:cellWidth state:aState
+    "draw a radio button"
+
+    |image
+     y "{ Class:SmallInteger }"
+     x "{ Class:SmallInteger }"
+     h "{ Class:SmallInteger }"
+     w "{ Class:SmallInteger }"|
+
+    w := radioButtonActiveImage extent x.
+    h := radioButtonActiveImage extent y.
+    y := yTop + ((rowHeight - h) // 2).
+    x := xLeft + ((cellWidth - w) // 2).
+    h odd ifTrue:[y := y + 1].
+
+    image := (aState ? false) 
+                ifTrue:radioButtonActiveImage
+                ifFalse:radioButtonPassiveImage.
+
+    image := image onDevice:device.
+
+    self displayForm:image x:x y:y.
 ! !
 
 !DSVColumnView methodsFor:'enumerating columns'!
 
-columnsDo:aOneArgBlock 
-    "evaluate the argument, aOneArgBlock for every column"
+columnsDo:aOneArgBlock
+    "evaluate the argument, aOneArgBlock for every columnDescriptor"
     
     columnDescriptors do:aOneArgBlock
 !
@@ -2250,9 +2318,11 @@
 
     ((button == 2) or:[button == #menu]) ifTrue:[ |menu|
         menu := self findMenuForSelection.
-
-        menu notNil ifTrue:[ self startUpMenu:menu ]
-                   ifFalse:[ super buttonPress:button x:x y:y ].
+        menu notNil ifTrue:[ 
+            self startUpMenu:menu.
+            ^ self
+        ].
+        super buttonPress:button x:x y:y.
         ^ self
     ].
 
@@ -2287,12 +2357,17 @@
         ].
         self selectRowAt:rowNr colAt:colNr atPoint:clickPoint openEditor:false.
 
-        buttonReleaseAction := [ self selectRowAt:rowNr colAt:colNr atPoint:clickPoint openEditor:true ].
-        buttonMotionAction := [:aPoint|
-            (self canStartDragAt:aPoint clickedAt:clickPoint) ifTrue:[
-                self startDragAt:aPoint
-            ]
-        ].
+        buttonReleaseAction := 
+            [ 
+                self selectRowAt:rowNr colAt:colNr atPoint:clickPoint openEditor:true 
+            ].
+
+        buttonMotionAction := 
+            [:aPoint|
+                (self canStartDragAt:aPoint clickedAt:clickPoint) ifTrue:[
+                    self startDragAt:aPoint
+                ]
+            ].
         ^ self
     ].
 
@@ -2393,7 +2468,7 @@
     colNr isNil ifTrue:[ ^ self ].
 
     rowNr  := self lastIndexSelected.
-    column := self columnAt:colNr.
+    column := self columnDescriptorAt:colNr.
     found  := 0.
 
     lsize > rowNr ifTrue:[
@@ -2550,12 +2625,14 @@
     self numberOfSelections == 1 ifTrue:[
         row := self at:(self firstIndexSelected).
         col := self selectedColumn.
-        (col notNil 
-            and:[ (menu := col menuForRow:row orAdaptor:columnAdaptor) notNil ]) 
-                ifTrue:[ ^ menu ].
+        col notNil ifTrue:[
+            menu := col menuForRow:row orAdaptor:columnAdaptor.
+            menu notNil ifTrue:[ ^ menu ].
+        ].
+
         col := columnDescriptors 
-                    detect:[:c | c rendererType == #rowSelector ]
-                    ifNone:[ nil ].
+                        detect:[:c | c rendererType == #rowSelector ]
+                        ifNone:[ nil ].
         col notNil ifTrue:[
             ^ col menuForRow:row inApplication:(self application)
         ]
@@ -2682,7 +2759,7 @@
 
                 selColNr := maxColNr
             ].
-            column := self columnAt:selColNr.
+            column := self columnDescriptorAt:selColNr.
 
             (column rendererType ~~ #rowSelector and:[column canSelect:selRowNr]) ifTrue:[
                 ^ self selectColIndex:selColNr rowIndex:selRowNr.
@@ -2712,7 +2789,7 @@
 
             selColNr := 1
         ].
-        column := self columnAt:selColNr.
+        column := self columnDescriptorAt:selColNr.
 
         (column rendererType ~~ #rowSelector and:[column canSelect:selRowNr]) ifTrue:[
             ^ self selectColIndex:selColNr rowIndex:selRowNr
@@ -2881,8 +2958,11 @@
     rowSelectorForm         := self imageOnMyDevice:rowSelectorForm.
     checkToggleActiveImage  := self imageOnMyDevice:checkToggleActiveImage.
     checkTogglePassiveImage := self imageOnMyDevice:checkTogglePassiveImage.
+    checkToggleForm         := self imageOnMyDevice:checkToggleForm.
+    radioButtonActiveImage  := self imageOnMyDevice:radioButtonActiveImage.
+    radioButtonPassiveImage := self imageOnMyDevice:radioButtonPassiveImage.
+    radioButtonForm         := self imageOnMyDevice:radioButtonForm.
     comboButtonForm         := self imageOnMyDevice:comboButtonForm.
-    checkToggleForm         := self imageOnMyDevice:checkToggleForm.
 !
 
 initStyle
@@ -2932,9 +3012,24 @@
     ].
 
     rowSelectorForm         := self class rowSelectorImage.
+
     checkToggleActiveImage  := CheckToggleActiveImage.
     checkTogglePassiveImage := CheckTogglePassiveImage.
 
+    CheckToggleForm isNil ifTrue:[
+        widget            := CheckToggle new.
+        CheckToggleForm   := widget label.
+        CheckToggleLevel  := widget offLevel.
+        CheckToggleExtent := widget preferredExtent.
+    ].
+
+    checkToggleForm   := CheckToggleForm.
+    checkToggleLevel  := CheckToggleLevel.
+    checkToggleExtent := CheckToggleExtent.
+
+    radioButtonActiveImage  := RadioButtonActiveImage.
+    radioButtonPassiveImage := RadioButtonPassiveImage.
+
     ComboButtonForm isNil ifTrue:[
         widget            := ComboListView new.
         button            := widget menuButton.
@@ -2943,19 +3038,9 @@
         ComboButtonExtent := (button preferredWidth) @ (widget preferredHeight).
     ].
 
-    CheckToggleForm isNil ifTrue:[
-        widget            := CheckToggle new.
-        CheckToggleForm   := widget label.
-        CheckToggleLevel  := widget offLevel.
-        CheckToggleExtent := widget preferredExtent.
-    ].
     comboButtonForm   := ComboButtonForm.
     comboButtonLevel  := ComboButtonLevel.
     comboButtonExtent := ComboButtonExtent.
-
-    checkToggleForm   := CheckToggleForm.
-    checkToggleLevel  := CheckToggleLevel.
-    checkToggleExtent := CheckToggleExtent.
 !
 
 initialize
@@ -3957,7 +4042,7 @@
 !
 
 openEditorOnSelection
-     |colIdx column rowIdx editSpec sensor winGroup
+     |colIdx column rowIdx editSpec winGroup
       edView filter keyBrdFwd selColor|
 
     (shown and:[editView isNil]) ifFalse:[
@@ -3967,7 +4052,7 @@
     winGroup isNil ifTrue:[^ self ].
 
     colIdx := self selectedColIndex ? 0.
-    column := self columnAt:colIdx.
+    column := self columnDescriptorAt:colIdx.
     column isNil ifTrue:[^ self].
 
     rowIdx := self selectedRowIndex ? 0.
@@ -3983,7 +4068,8 @@
         self scrollToRowAt:rowIdx colAt:colIdx.
     ].
 
-    editView := SimpleView extent:((column width - (2 * separatorSize)) 
+    editView := SimpleView 
+                extent:((column width - (2 * separatorSize)) 
                         @ (rowHeight - (2 * separatorSize)))
                 in:self.
 
@@ -4020,12 +4106,33 @@
     edView canTab:true.
     winGroup focusView:edView.
 
+    self processAllExposeEvents.
+!
+
+processAllExposeEvents
+    |sensor|
+
     sensor := self sensor.
-
-    [ (sensor hasExposeEventFor:nil)
+    [ 
+        sensor hasExposeEventFor:nil
     ] whileTrue:[
-        winGroup processExposeEvents
-    ].
+        self windowGroup processExposeEvents
+    ].
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
 !
 
 removeRowFromSelection:aRowNr
@@ -4104,8 +4211,20 @@
         "/ simulate clicking into the editor
         self sensor 
                 pushEvent:(WindowEvent   buttonPress:#select x:p x y:p y view:view);
-                pushEvent:(WindowEvent buttonRelease:#select x:p x y:p y view:view)
-    ].
+                pushEvent:(WindowEvent buttonRelease:#select x:p x y:p y view:view).
+
+"/        "/ a very special hack for radioButtons:
+"/        "/ if the button is now on, all other cells must be turned off !!
+"/        self selectedColumn editorType == #RadioButton ifTrue:[
+"/            1 tolist size do:[:eachRowNr |
+"/                eachRowNr ~~ rowNr ifTrue:[
+"/                    self at:eachRowNr put:false
+"/                ].
+"/            ].
+"/        ].
+    ].
+
+
 !
 
 selectRowFrom:start to:stop 
@@ -4250,7 +4369,7 @@
 setSelectColIndex:colNrArg rowIndex:rowNrArg openEditor:openEditor
     "change selection without notification"
 
-    |rowNr colNr newCol oldCol oldRow sensor sglSelRow oldSz winGroup|
+    |rowNr colNr newCol oldCol oldRow sglSelRow oldSz winGroup|
 
     rowNr := self validateSelection:rowNrArg.
     colNr := colNrArg.
@@ -4264,7 +4383,7 @@
         ].
     ].
     (colNr := colNr ? 0) ~~ 0 ifTrue:[
-        newCol := self columnAt:colNr.
+        newCol := self columnDescriptorAt:colNr.
         newCol rendererType == #rowSelector ifTrue:[
             colNr := 0.
             newCol := nil
@@ -4337,11 +4456,8 @@
         self selectionIndicesDo:[:i | self invalidateRowAt:i colAt:0 ].
         self scrollToRowAt:(self firstIndexSelected) colAt:0
     ].
-    sensor := self sensor.
-    [ sensor hasExposeEventFor:nil
-    ] whileTrue:[
-        winGroup processExposeEvents
-    ].
+
+    self processAllExposeEvents.
 
     "Modified: / 23-10-2006 / 10:56:20 / cg"
 !
@@ -4378,7 +4494,7 @@
             "/ ]
             selRow := selRow first
         ].
-        (self columnAt:selCol) at:selRow put:edValue.
+        (self columnDescriptorAt:selCol) at:selRow put:edValue.
         modifiedChannel notNil ifTrue:[
             modifiedChannel value:true
         ].
@@ -4430,5 +4546,5 @@
 !DSVColumnView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/DSVColumnView.st,v 1.237 2008-07-24 12:43:54 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/DSVColumnView.st,v 1.238 2008-07-25 12:43:47 cg Exp $'
 ! !