DSVColumnView.st
author ca
Thu, 16 Apr 1998 13:00:21 +0200
changeset 861 a227a3ca27e7
parent 859 e63eb6f321e1
child 872 ad92183a6e6b
permissions -rw-r--r--
bug fix in multi selection

"
 COPYRIGHT (c) 1997 by Claus Gittinger / eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"




View subclass:#DSVColumnView
	instanceVariableNames:'editValue editView multipleSelectOk selectedColIndex
		selectedRowIndex rowHeight columnDescriptors viewOrigin colorMap
		lockRowIndex rowIfAbsentBlock columnHolder registererImages list
		fgColor canFit separatorSize catchChangeEvents beDependentOfRows
		bgColor hgLgFgColor hgLgBgColor actionBlock
		doubleClickActionBlock verticalSpacing horizontalSpacing
		rowSelectorForm buttonLightColor buttonShadowColor
		buttonHalfLightColor buttonHalfShadowColor checkToggleExtent
		checkToggleForm checkToggleLevel comboButtonExtent
		comboButtonForm comboButtonLevel clickPosition dragAccessPoint
		dragIsActive dropTarget dropSource'
	classVariableNames:'DefaultForegroundColor DefaultBackgroundColor
		DefaultHilightForegroundColor DefaultHilightBackgroundColor
		RowSelector ButtonLightColor ButtonShadowColor
		ButtonHalfLightColor ButtonHalfShadowColor ButtonEdgeStyle'
	poolDictionaries:''
	category:'Views-DataSet'
!

!DSVColumnView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1997 by Claus Gittinger / eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"



!

documentation
"
    implements a scrollable selection view based on rows and columns

    [Instance variables:]

        editValue               <Model>                 current editing model
        editView                <View>                  current editing component
        selectedColIndex        <Integer>               selected column index or 0
        selectedRowIndex        <Integer>               selected row index or 0
        rowHeight               <Integer>               maximum height of any row
        columnDescriptors       <SequancableCollection> list of column descriptors
        list                    <SequancableCollection> list of rows
        fgColor                 <Color>                 foreground color
        registererImages        <IdentityDictionary>    list of images registered on the device
        beDependentOfRows       <Coolean>               keep rows dependent; on default is disabled.
                                                        in case of enabled a row can raise a change
                                                        notification whithout a parameter which
                                                        will force a redraw of the row or the
                                                        readSelector of the column which will
                                                        redraw the cell in the row only.

    [author:]
        Claus Atzkern

    [see also:]
        DataSetColumnSpec
        DataSetColumn
        DataSetView
"

! !

!DSVColumnView class methodsFor:'accessing forms'!

rowSelector

    RowSelector isNil ifTrue:[
        RowSelector := Form
                          width:8
                         height:11
                      fromArray:#[2r01000000
                                  2r01100000
                                  2r01110000
                                  2r01111000
                                  2r01111100
                                  2r01111110
                                  2r01111100
                                  2r01111000
                                  2r01110000
                                  2r01100000
                                  2r01000000]
                             on:Display.

        RowSelector := RowSelector asImage.
    ].
    ^ RowSelector

! !

!DSVColumnView class methodsFor:'defaults'!

horizontalSpacing
    ^ 4

!

updateStyleCache
    "extract values from the styleSheet and cache them in class variables
    "
    <resource: #style (#textForegroundColor #'scrollableView.backgroundColor'
                       #'selection.hilightForegroundColor'
                       #'selection.hilightBackgroundColor'   )>

    DefaultForegroundColor        := StyleSheet colorAt:'textForegroundColor' default:(Color black).
    DefaultBackgroundColor        := StyleSheet colorAt:'scrollableView.backgroundColor' default:DefaultViewBackgroundColor.

    DefaultHilightForegroundColor := StyleSheet colorAt:'selection.hilightForegroundColor' default:DefaultForegroundColor.
    DefaultHilightBackgroundColor := StyleSheet colorAt:'selection.hilightBackgroundColor' default:(Color veryLightGrey).

    DefaultHilightForegroundColor = DefaultHilightBackgroundColor ifTrue:[
        DefaultHilightBackgroundColor := Color veryLightGrey
    ].
    ButtonLightColor      := StyleSheet colorAt:'button.lightColor'.
    ButtonShadowColor     := StyleSheet colorAt:'button.shadowColor'.
    ButtonHalfLightColor  := StyleSheet colorAt:'button.halfLightColor'.
    ButtonHalfShadowColor := StyleSheet colorAt:'button.halfShadowColor'.
    ButtonEdgeStyle       := StyleSheet at:'button.edgeStyle'.

"
self updateStyleCache.
"

    "Modified: / 26.10.1997 / 17:09:07 / cg"
!

verticalSpacing
    ^ 2

! !

!DSVColumnView class methodsFor:'resources'!

dragIconMulti
    "Generated by the Image Editor"
    "
    ImageEditor openOnClass:self andSelector:#dragIconMulti
    "

    <resource: #image>

    ^Icon
        constantNamed:#'DSVColumnView dragIconMulti'
        ifAbsentPut:[(Depth8Image new) width: 32; height: 32; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@A@PDA@PDA@PDA@PDA@PDA@PDA@P@@@@@@@@@@@@@@@@DA@PDA@PDA@PDA@PDA@PDA@PDA@@@@@@@@@@@@@@@@@PDB@ HB@ HB@ HB@ HB@ DA@ HA@P@@@@@@@@@@@@@A@PHB@ HB@ HB@ HB@ HB@PDB@ DA@@@@@@@@@@@@@@DA@ HB@ DA@PDA@PDA@PDA@PDA@PDA@PDA@@@@@@@@@PDB@ HB@PDA@PDA@PDA@PDA@PDA@PDA@PD@@@@@@@@A@PHB@ HA@PHB@ HB@ HB@ HB@ HB@PDB@ DA@@@@@@DA@ HB@ DA@ HB@ HB@ HB@ HB@ HA@PHB@PD@@@@@@PDB@ HB@PDB@ HB@ HB@ HB@ HB@ DA@ HB@ DA@@@A@PHB@ HA@PHB@ HB@ HB@ HB@ HB@PDB@ HB@PD@@@DA@ HB@ DA@ HB@ HB@ HB@ HB@ HA@PDA@PDA@PDA@PDB@ HB@PDB@ HB@ HB@ HB@ HB@ DA@PDA@PDA@PDA@PHB@ HA@PHB@ HB@ HB@ HB@ HB@ HB@ HB@ HA@PDA@ HB@ DA@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ DA@PDB@ HB@PDB@ HB@ HB@ HB@ HB@ HB@ HB@ HB@PDA@PHB@ HA@PHB@ HB@ HB@ HB@ HB@ HB@ HB@ HA@PDA@ HB@ DA@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ DA@PDB@ HB@PDB@ HB@ HB@ HB@ HB@ HB@ HB@ HB@PDA@PDA@PDA@PHB@ HB@ HB@ HB@ HB@ HB@ HB@ HA@PDA@PDA@PDA@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ DA@@@@@@@@@PDB@ HB@ HB@ HB@ HB@ HB@ HB@ HB@PD@@@@@@@@A@PHB@ HB@ HB@ HB@ HB@ HB@ HB@ HA@P@@@@@@@@DA@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PDA@@@@@@@@@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PD@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 0 0 0 255 255 255]; mask:((ImageMask new) width: 32; height: 32; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@@@@@@@@@@O??<@C???@@???<@O???@C????@????0O????C????0?????O????3?????????????????????????????????????????????????????@????0O???<C????@????0@@@@@@@@@@@@@@@@@@@@@b') ; yourself); yourself]!

dragIconSingle
    "Generated by the Image Editor"
    "
    ImageEditor openOnClass:self andSelector:#dragIconSingle
    "

    <resource: #image>

    ^Icon
        constantNamed:#'DSVColumnView dragIconSingle'
        ifAbsentPut:[(Depth8Image new) width: 32; height: 32; photometric:(#palette); bitsPerSample:(#(8 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@A@PDA@PDA@PDA@PDA@PDA@PDA@P@@@@@@@@@@@@@@@@DA@PDA@PDA@PDA@PDA@PDA@PDA@@@@@@@@@@@@@@@@@PDB@ HB@ HB@ HB@ HB@ DA@ HA@P@@@@@@@@@@@@@A@PHB@ HB@ HB@ HB@ HB@PDB@ DA@@@@@@@@@@@@@@DA@ HB@ HB@ HB@ HB@ HA@PHB@ HA@P@@@@@@@@@@@PDB@ HB@ HB@ HB@ HB@ DA@ HB@ DA@@@@@@@@@@@A@PHB@ HB@ HB@ HB@ HB@PDA@PDA@PDA@P@@@@@@@@DA@ HB@ HB@ HB@ HB@ HA@PDA@PDA@PDA@@@@@@@@@PDB@ HB@ HB@ HB@ HB@ HB@ HB@ HB@PD@@@@@@@@A@PHB@ HB@ HB@ HB@ HB@ HB@ HB@ HA@P@@@@@@@@DA@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ DA@@@@@@@@@PDB@ HB@ HB@ HB@ HB@ HB@ HB@ HB@PD@@@@@@@@A@PHB@ HB@ HB@ HB@ HB@ HB@ HB@ HA@P@@@@@@@@DA@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ DA@@@@@@@@@PDB@ HB@ HB@ HB@ HB@ HB@ HB@ HB@PD@@@@@@@@A@PHB@ HB@ HB@ HB@ HB@ HB@ HB@ HA@P@@@@@@@@DA@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ DA@@@@@@@@@PDB@ HB@ HB@ HB@ HB@ HB@ HB@ HB@PD@@@@@@@@A@PHB@ HB@ HB@ HB@ HB@ HB@ HB@ HA@P@@@@@@@@DA@ HB@ HB@ HB@ HB@ HB@ HB@ HB@ DA@@@@@@@@@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PD@@@@@@@@A@PDA@PDA@PDA@PDA@PDA@PDA@PDA@PDA@P@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 0 0 0 255 255 255]; mask:((ImageMask new) width: 32; height: 32; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@@@@@@@@@@O??<@C???@@???<@O???@C???<@????@O???<C????@????0O???<C????@????0O???<C????@????0O???<C????@????0O???<C????@????0O???<@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@b') ; yourself); yourself]! !

!DSVColumnView methodsFor:'accessing actions'!

action:aOneArgAction
    "set the action block to be performed on select
    "
    actionBlock := aOneArgAction


!

doubleClickAction:aOneArgAction
    "set the action block to be performed on doubleclick
    "
    doubleClickActionBlock := aOneArgAction


!

rowIfAbsent:aOneArgAction
    "set the action block to be performed on each 'nil' entry into the
     list. The argument to the block is the index into the list. The
     block returns the row which is put to the list
    "
    rowIfAbsentBlock := 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'
     is redrawn. In case of a nil readSelector, the whole raw is redrawn.
        -> row changed:'what'
     On default the attribute is set to true (enabled).
    "
    ^ beDependentOfRows
!

beDependentOfRows:aBool
    "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'
     is redrawn. In case of a nil readSelector, the whole raw is redrawn.
        -> row changed:'what'
     On default the attribute is set to true (enabled).
    "
    aBool ~~ beDependentOfRows ifTrue:[
        beDependentOfRows := aBool.

        self size ~~ 0 ifTrue:[
            list do:[:aRow| aRow notNil ifTrue:[
                beDependentOfRows ifTrue:[aRow addDependent:self]
                                 ifFalse:[aRow removeDependent:self]
                ]
            ]
        ]
    ]
!

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 colors'!

backgroundColor
    "get the background color of the rows
    "
    ^ bgColor


!

backgroundColor:aColor
    "set the background color of the rows
    "
    bgColor ~~ aColor ifTrue:[
        super viewBackground:bgColor.

        self realized ifTrue:[
            bgColor := aColor on:device.
            self invalidate
        ] ifFalse:[
            bgColor := aColor
        ]
    ]
!

foregroundColor
    "return the foreground color of the rows
    "
    ^ fgColor

!

foregroundColor:aColor
    "set the foreground color of the rows
    "
    fgColor ~~ aColor ifTrue:[
        self realized ifTrue:[
            fgColor := aColor on:device.
            self invalidate
        ] ifFalse:[
            fgColor := aColor
        ]
    ]

!

hgLgBgColor
    "returns the background color of a selected row
    "
    ^ hgLgBgColor
!

hgLgFgColor
    "returns the foreground color of a selected row
    "
    ^ hgLgFgColor
!

separatorDarkColor
    "returns the dark color used for drawing a shadowed separator (3D)
    "
    ^ shadowColor


!

separatorLightColor
    "returns the light color used for drawing a shadowed separator (3D)
    "
    ^ lightColor


! !

!DSVColumnView methodsFor:'accessing columns'!

columnAt:anIndex
    "returns the column at an index
    "
    ^ columnDescriptors at:anIndex
!

columnDescriptors:colDesc
    "set the columnDescriptors
    "
    |id sz|

    sz := colDesc size.

    (sz == 0 or:[selectedColIndex ~~ 0]) ifTrue:[       "/ cell selected
        self deselect                                   "/ remove selection
    ].
    catchChangeEvents := true.

    sz ~~ 0 ifTrue:[
        id := 0.

        columnDescriptors := colDesc collect:[:aCol|
            id := id + 1.
            DataSetColumn new on:self description:aCol columnNumber:id.
        ]
    ] ifFalse:[
        columnDescriptors := #()
    ].
    canFit := (columnDescriptors findFirst:[:aCol|aCol canResize]) ~~ 0.
    preferredExtent := nil.

    shown ifTrue:[
        self fitColumns ifFalse:[
            self invalidate.
            self contentsChanged.
        ] ifTrue:[
            self preferredExtentChanged.
        ]
    ].
    catchChangeEvents := false.
    self changed:#sizeOfColumns.


!

firstColumn
    "returns the first column
    "
    ^ columnDescriptors at:1

!

lastColumn
    "returns the last column
    "
    ^ columnDescriptors last

! !

!DSVColumnView methodsFor:'accessing interactors'!

checkToggleExtent
    ^ checkToggleExtent
!

checkToggleForm
    ^ checkToggleForm
!

checkToggleLevel
    ^ checkToggleLevel
!

comboButtonExtent
    ^ comboButtonExtent
!

comboButtonForm
    ^ comboButtonForm
!

comboButtonLevel
    ^ comboButtonLevel
!

rowSelectorExtent
    "returns the bitmap of a selected row
    "
    ^ rowSelectorForm extent
!

rowSelectorForm
    "returns the bitmap of a selected row
    "
    rowSelectorForm isNil ifTrue:[
        rowSelectorForm := (self class rowSelector) on:device
    ].
    ^ rowSelectorForm
! !

!DSVColumnView methodsFor:'accessing mvc'!

columnHolder
    ^ columnHolder

!

columnHolder:aValueHolder
    |columns|

    columnHolder notNil ifTrue:[
        columnHolder removeDependent:self
    ].

    (columnHolder := aValueHolder) notNil ifTrue:[
        columnHolder addDependent:self.
        columns := columnHolder value.

        columns notNil ifTrue:[
            self columnDescriptors:columns
        ]
    ].

! !

!DSVColumnView methodsFor:'accessing rows'!

at:aRowNr
    "return the row at an index, aRowNr
    "
    |row|

    (row := list at:aRowNr) isNil ifTrue:[
        lockRowIndex := aRowNr.

        (row := rowIfAbsentBlock value:aRowNr) notNil ifTrue:[
            list at:aRowNr put:row.
            beDependentOfRows ifTrue:[row addDependent:self].
        ].

        lockRowIndex := 0
    ].
    ^ row
!

at:aRowNr ifAbsent:exceptionBlock
    "return the row at a aRowNr. If the index is invalid, return the
     result of evaluating the exceptionblock
    "
    (aRowNr between:1 and:self size) ifTrue:[
        ^ self at:aRowNr
    ].
    ^ exceptionBlock value
!

at:aRowNr put:aRow
    "change the row at an index. The added row is returned
    "
    |row|

    lockRowIndex == aRowNr ifTrue:[
        ^ self
    ].
    row := list at:aRowNr.
    row == aRow ifTrue:[
        ^ self
    ].

    beDependentOfRows ifTrue:[
        (row := list at:aRowNr) notNil ifTrue:[
            row removeDependent:self
        ]
    ].

    list at:aRowNr put:aRow.

    aRow notNil ifTrue:[                "/ free list
        beDependentOfRows ifTrue:[
            aRow addDependent:self
        ].
        self redrawRowAt:aRowNr
    ].
    ^ aRow.
!

first
    "return the first row
    "
    ^ self at:1
!

identityIndexOfRow:aRow
    "returns index of a row or 0
    "
    (list size ~~ 0 and:[aRow notNil]) ifTrue:[
        ^ list identityIndexOf:aRow
    ].
    ^ 0
!

last
    "return the last row
    "
    ^ self at:(self size)
!

list
    "get the list of rows
    "
    ^ list



!

list:aList
    "set the list of rows
    "
    |makeDependent|

    "/ remove selection without redraw

    editValue notNil ifTrue:[
        editValue removeDependent:self.
        editValue := nil
    ].

    editView notNil ifTrue:[
        editView destroy.
        editView := nil.
    ].

    selectedColIndex := 0.
    selectedRowIndex := multipleSelectOk ifTrue:[nil] ifFalse:[0].

    shown ifFalse:[
        preferredExtent := nil
    ] ifTrue:[
        aList size ~~ 0 ifTrue:[  "/ otherwise keep old values
            self columnsDo:[:aCol| aCol invalidate ].
            preferredExtent := nil.
        ]
    ].

    (makeDependent := beDependentOfRows) ifTrue:[
        self beDependentOfRows:false.
    ].

    aList size ~~ 0 ifTrue:[
        list := OrderedCollection new:(aList size).
        aList do:[:el| list add:el ].
    ] ifFalse:[
        list := nil
    ].
    self beDependentOfRows:makeDependent.

    shown ifTrue:[
        list size ~~ 0 ifTrue:[
            self fitColumns ifTrue:[^ self ].
        ].
        self recomputeHeightOfContents.
        self invalidate.
        self contentsChanged.
    ].




! !

!DSVColumnView methodsFor:'accessing visibility'!

font:aFont
    "set the font for all shown rows.
    "
    (aFont notNil and:[aFont ~~ font]) ifTrue:[
        super font:(aFont on:device).
        self columnsDo:[:aCol| aCol invalidate ].
        self preferredExtentChanged.

        realized ifTrue:[
            self invalidate.
            self contentsChanged
        ]
    ]

!

has3Dseparators
    "returns true if shown in 3D mode
    "
    ^ separatorSize ~~ 1
!

has3Dseparators:aBool
    "enable or disable 3D mode
    "
    |newSepSize|

    newSepSize := aBool ifTrue:[2] ifFalse:[1].

    newSepSize ~~ separatorSize ifTrue:[
        separatorSize := newSepSize.
        
        self columnsDo:[:aCol| aCol invalidate ].
        self preferredExtentChanged.

        realized ifTrue:[
            self invalidate.
            self contentsChanged
        ]
    ]


!

horizontalSpacing
    "horizontal spacing used by columns
    "
    ^ horizontalSpacing
!

horizontalSpacing:aNumber
    "horizontal spacing used by columns
    "
    horizontalSpacing ~~ aNumber ifTrue:[
        horizontalSpacing := aNumber.
        self preferredExtentChanged.
    ].
!

verticalSpacing
    "vertical spacing used by columns
    "
    ^ verticalSpacing
!

verticalSpacing:aNumber
    "vertical spacing used by columns
    "
    verticalSpacing ~~ aNumber ifTrue:[
        verticalSpacing := aNumber.
        self preferredExtentChanged.
    ].
! !

!DSVColumnView methodsFor:'adding & removing rows'!

add:aRow
    "insert row at end
    "
    ^ self add:aRow beforeIndex:(1 + self size)
!

add:aRow afterIndex:aRowNr
    "add a new row after slot aRowNr and redisplay; returns nil in case
     of an invalid index or the row
    "
    ^ self add:aRow beforeIndex:(aRowNr + 1)
!

add:aRow beforeIndex:aRowNr
    "add a new row before slot aRowNr and redisplay; returns nil in case
     of an invalid index or the row
    "
    self addAll:(Array with:aRow) beforeIndex:aRowNr.
    ^ aRow.
!

addAll:aList beforeIndex:start
    "add a collection of rows before slot start and redisplay
    "
    |y0 y1 yD h dH size noSel|

    (size := aList size) == 0 ifTrue:[
        ^ self
    ].

    self size == 0 ifTrue:[
        ^ self list:aList
    ].

    beDependentOfRows ifTrue:[
        aList do:[:aRow| aRow notNil ifTrue:[aRow addDependent:self]]
    ].

    noSel := self numberOfSelections.

    noSel ~~ 0 ifTrue:[
        multipleSelectOk ifFalse:[
            selectedRowIndex >= start ifTrue:[
                selectedRowIndex := selectedRowIndex + size
            ]
        ] ifTrue:[
            1 to:noSel do:[:i||v|
                (v := selectedRowIndex at:i) >= start ifTrue:[
                    selectedRowIndex at:i put:(v + size)
                ]
            ]
        ]
    ].
    list addAll:aList beforeIndex:start.
    self recomputeHeightOfContents.

    y0 := (start - 1) * rowHeight.
    yD := size * rowHeight.
    y1 := y0 + yD.

    y0 < viewOrigin y ifTrue:[
        self originWillChange.
        viewOrigin y:(yD + viewOrigin y).
        self originChanged:(0 @ yD).
    ].

    (shown not or:[self sensor hasDamageFor:self]) ifTrue:[
        ^ self contentsChanged.
    ].

    y0 := self yVisibleOfRowNr:start.
    y1 := y0 + yD.

    (y1 > margin and:[y0 < (h := height - margin)]) ifTrue:[
        h  := h - y1.
        y0 := y0 max:margin.
        dH := y1 - y0.

        start == list size ifFalse:[
            self catchExpose.

            self copyFrom:self x:0 y:y0
                             toX:0 y:y1
                           width:width height:h async:true.

            self waitForExpose
        ].
        self redrawX:margin y:y0 width:width - margin - margin height:dH.
    ].
    self contentsChanged.

!

addFirst:aRow
    "insert a row at start
    "
    ^ self add:aRow beforeIndex:1
!

removeFirst
    "remove first row; returns the removed row
    "
    self removeIndex:1
!

removeFrom:startIndex to:stopIndex
    "remove rows from start to stop
    "
    |coll noRedraw
     noSel "{ Class: SmallInteger }"
     size  "{ Class: SmallInteger }"
     start "{ Class: SmallInteger }"
     stop  "{ Class: SmallInteger }"
     y0    "{ Class: SmallInteger }"
     y1    "{ Class: SmallInteger }"
     oY    "{ Class: SmallInteger }"
     dY    "{ Class: SmallInteger }"
     yB    "{ Class: SmallInteger }"
     h     "{ Class: SmallInteger }"
    |

    (    (start := startIndex) < 1
     or:[(stop := stopIndex) > list size]
    ) ifTrue:[
        ^ self subscriptBoundsError:start
    ].
    size := stop - start + 1.

    beDependentOfRows ifTrue:[
        list from:start to:stop do:[:r| r notNil ifTrue:[r removeDependent:self]].
    ].
    noSel := self numberOfSelections.

    noSel ~~ 0 ifTrue:[
        noSel == 1 ifTrue:[
            noSel := self firstIndexSelected.

            noSel < start ifFalse:[
                noSel > stop ifTrue:[
                    noSel := noSel - size.

                    multipleSelectOk ifFalse:[selectedRowIndex := noSel]
                                      ifTrue:[selectedRowIndex at:1 put:noSel]
                ] ifFalse:[
                    editValue notNil ifTrue:[
                        editValue removeDependent:self.
                        editValue := nil.
                    ].
                    self deselect.
                ]
            ]
        ] ifFalse:[
            coll := OrderedCollection new:noSel.

            selectedRowIndex do:[:i|
                i < start ifTrue:[
                    coll add:i
                ] ifFalse:[
                    i > stop ifTrue:[
                        coll add:(i - size)
                    ]
                ]
            ].
            coll size == 0 ifTrue:[
                self deselect
            ] ifFalse:[
                selectedRowIndex := coll
            ]
        ]
    ].
    list removeFrom:start to:stop.

    y0 := start - 1 * rowHeight.
    dY := size * rowHeight.
    y1 := dY + y0.
    yB := y1 + margin - viewOrigin y.
    self recomputeHeightOfContents.

    y0 < (oY := viewOrigin y) ifTrue:[
        (noRedraw := y1 <= oY) ifFalse:[dY := y0 - oY]
                                ifTrue:[dY := dY negated].
        self originWillChange.
        viewOrigin y:(dY + oY).
        self originChanged:(0 @ dY).        
    ] ifFalse:[
        noRedraw := y0 > (height + viewOrigin y)
    ].

    (noRedraw or:[shown not]) ifFalse:[
        y1 := yB.
        y0 := self yVisibleOfRowNr:start.
        h  := height - margin - yB.
        y0 := y0 max:margin.

        h > 0 ifTrue:[
            self catchExpose.
            self copyFrom:self x:0 y:yB toX:0 y:y0 width:width height:h async:true.
            self waitForExpose.
        ].
        y0 := y0 + h.
        self redrawX:margin y:y0 width:width - margin - margin height:(height - y0).
    ].
    self contentsChanged.

!

removeIndex:aRowNr
    "remove row at an index; returns the removed row
    "
    |row|

    row := list at:aRowNr ifAbsent:nil.
    self removeFrom:aRowNr to:aRowNr.
  ^ row
!

removeLast
    "remove last row; the row is returned
    "
    ^ self removeIndex:self size
! !

!DSVColumnView methodsFor:'change & update'!

changed:aParameter with:anArgument
    "notify all dependents that the receiver has changed somehow.
     Each dependent gets a  '#update:with:from:'-message, with aParameter
     and anArgument as arguments."

    catchChangeEvents ifTrue:[
        (    aParameter == #sizeOfColumns
         or:[aParameter == #columnsLayout]
        ) ifTrue:[
            ^ self
        ]
    ].
    super changed:aParameter with:anArgument

!

update:something with:aParameter from:changedObject
    "one of my rows/cells changed its value
    "
    |row|

    changedObject == columnHolder ifTrue:[
        ^ self columnDescriptors:(columnHolder value)
    ].

    changedObject == editValue ifTrue:[
        ^ self selectedColumn at:(self firstIndexSelected) put:(editValue value)
    ].

    row := (something isNumber) ifTrue:[something] ifFalse:[changedObject].
    self redrawVisibleRow:row readSelector:aParameter.

! !

!DSVColumnView methodsFor:'defaults'!

updateStyleCache
    "extract values from the styleSheet and cache them in class variables
    "
    <resource: #style (#textForegroundColor #'scrollableView.backgroundColor'
                       #'selection.hilightForegroundColor'
                       #'selection.hilightBackgroundColor'   )>

    DefaultForegroundColor        := StyleSheet colorAt:'textForegroundColor' default:(Color black).
    DefaultBackgroundColor        := StyleSheet at:'scrollableView.backgroundColor' default:DefaultViewBackgroundColor.

    DefaultHilightForegroundColor := StyleSheet colorAt:'selection.hilightForegroundColor' default:DefaultForegroundColor.
    DefaultHilightBackgroundColor := StyleSheet colorAt:'selection.hilightBackgroundColor' default:(Color veryLightGrey).

    DefaultHilightForegroundColor = DefaultHilightBackgroundColor ifTrue:[
        DefaultHilightBackgroundColor := Color veryLightGrey
    ].

    ButtonLightColor  := StyleSheet at:'button.lightColor'.
    ButtonShadowColor := StyleSheet at:'button.shadowColor'.
    ButtonEdgeStyle   := StyleSheet at:'button.edgeStyle'.

"
self updateStyleCache.
"

    "Modified: / 26.10.1997 / 17:09:07 / cg"
! !

!DSVColumnView methodsFor:'drag & drop'!

canDrag
    "returns true if dragging is enabled
    "
    ^ dropSource notNil

!

dropSource
    "returns the dropSource or nil
    "
    ^ dropSource


!

dropSource:aDropSourceOrNil
    "set the dropSource or nil
    "
    dropSource := aDropSourceOrNil.


!

dropTarget
    "returns the dropTarget or nil
    "
    ^ dropTarget

!

dropTarget:aDropTragetOrNil
    "set the dropTarget or nil
    "
    dropTarget := aDropTragetOrNil.

!

startDragAt:aPoint
    (dragIsActive not and:[dropSource notNil]) ifTrue:[
        dragIsActive := true.
        dropSource startDragIn:self at:aPoint
    ]

! !

!DSVColumnView methodsFor:'drawing'!

colorOnDevice:aColor
    "returns color on device
    "
    |col|

    aColor = Color noColor ifFalse:[
        col := colorMap at:aColor ifAbsent:nil.

        col isNil ifTrue:[
            colorMap at:aColor put:(col := aColor on:device)
        ].
        ^ col
    ].
    ^ bgColor
!

drawEdgesAtX:x y:y width:w height:h level:aLevel
    "draw edges
    "
    self drawEdgesAtX:x y:y width:w height:h level:aLevel on:self
!

drawEdgesAtX:x y:y width:w height:h level:aLevel on:aGC
    "draw edges
    "
    aGC  drawEdgesForX:x
                     y:y 
                 width:w
                height:h
                 level:aLevel 
                shadow:buttonShadowColor 
                 light:buttonLightColor
            halfShadow:buttonHalfShadowColor 
             halfLight:buttonHalfLightColor
                 style:ButtonEdgeStyle.

!

forceRedraw
    "a redraw forced by any other component
    "
    self redraw
!

invalidate
    "recompute extent before repair range
    "
    self  recomputeHeightOfContents.
    super invalidate.


!

redraw
    "redraw complete view
    "
    self redrawX:0 y:0 width:width height:height.

!

redrawRowAt:aRowNr
    "redraw total row at an index
    "
    self redrawRowAt:aRowNr colAt:0
!

redrawRowAt:aRowNr colAt:aColNr
    "redraw visible row in case of aColNr == 0 or the column in a row;
     in case that the row/column is hidden no redraw is done
    "
    |x y h w|

    (shown and:[aRowNr between:1 and:self size]) ifTrue:[
        h := rowHeight - 1.

        (y := self yVisibleOfRowNr:aRowNr) < margin ifTrue:[
            (h := h + y) <= margin ifTrue:[
                ^ self
            ].                                                  "/ row not visible
            h := h - margin.
            y := margin.
        ] ifFalse:[
            y >= height ifTrue:[^ self].
        ].
        aColNr ~~ 0 ifTrue:[                                    "/ redraw column in row
            w := (self columnAt:aColNr) width.

            (x := self xVisibleOfColNr:aColNr) < margin ifTrue:[
                (w := w + x) <= margin ifTrue:[
                    ^ self
                ].                                              "/ column not visible
                w := w - margin.
                x := margin.
            ] ifFalse:[
                x >= width ifTrue:[^ self].
            ]
        ] ifFalse:[                                             "/ redraw whole row
            x := margin.
            w := width.
        ].
        self redrawX:x y:y width:w height:h
    ]
!

redrawVisibleRow:aRow
    "redraw row if visible
    "
    self redrawVisibleRow:aRow colAt:0

!

redrawVisibleRow:aRow colAt:aColNr
    "redraw row if visible
    "
    |start "{ Class:SmallInteger }"
     stop  "{ Class:SmallInteger }"
    |

    (start := self indexOfFirstRowShown) ~~ 0 ifTrue:[
        stop := (start + (height // rowHeight)) min:(self size).

        aRow isNumber ifTrue:[
            (aRow between:start and:stop) ifTrue:[
                self redrawRowAt:aRow colAt:aColNr
            ]
        ] ifFalse:[
            start to:stop do:[:i|
                (self at:i) == aRow ifTrue:[
                    ^ self redrawRowAt:i colAt:aColNr
                ]
            ]
        ]
    ]


!

redrawVisibleRow:aRow readSelector:aSelector
    "redraw a column identified by its read selector; if no column with
     the specified read selector is detected, the whole line is drawn.
    "
    |row idx|

    aSelector isNil ifTrue:[
        idx := 0
    ] ifFalse:[
        (row := aRow) isNumber ifTrue:[
            (row := self at:aRow) isNil ifTrue:[ ^ self ]
        ].
        idx := columnDescriptors findFirst:[:aCol||desc|
            aCol description readSelector == aSelector
        ]
    ].
    self redrawVisibleRow:aRow colAt:idx




!

redrawX:x y:y width:w height:h
    "redraw part of myself immediately, given logical coordinates 
    "
    |c0 savClip
     start "{ Class:SmallInteger }"
     stop  "{ Class:SmallInteger }"
     x0    "{ Class:SmallInteger }"
     x1    "{ Class:SmallInteger }"
     maxX  "{ Class:SmallInteger }"
     minX  "{ Class:SmallInteger }"
     yTop  "{ Class:SmallInteger }"
     yBot  "{ Class:SmallInteger }"
     times "{ Class:SmallInteger }"
     yMax  "{ Class:SmallInteger }"
    |

    shown ifFalse:[^ self].

    self paint:bgColor.
    self fillRectangleX:x y:y width:w height:h.

    columnDescriptors size ~~ 0 ifTrue:[                
        savClip := clipRect.
        self clippingRectangle:(Rectangle left:x top:y width:w height:h).

        yTop  := margin - viewOrigin y.                   
        c0    := y - yTop max:0.
        start := (c0 // rowHeight) + 1.
        stop  := (c0 + h - 1 // rowHeight + 1) min:(list size).

        (times := stop - start + 1) > 0 ifTrue:[
            maxX := (x + w) min:(width - margin).
            x0   := margin - viewOrigin x.
            yTop := yTop + ((start - 1) * rowHeight).
            yBot := yTop + (times * rowHeight).
            yMax := height - margin - margin.
            minX := x max:margin.

            columnDescriptors do:[:aCol|
                x1 := x0 + aCol width.

                (x1 > x and:[x0 < maxX]) ifTrue:[
                    aCol drawFrom:start times:times x0:x0 yTop:yTop yBot:yBot with:fgColor and:bgColor.
                ].
                x0 := x1
            ]
        ].
        self clippingRectangle:savClip.
    ].
! !

!DSVColumnView methodsFor:'enumerating columns'!

columnsDo:aOneArgBlock
    "evaluate the argument, aOneArgBlock for every column
    "
    columnDescriptors do:aOneArgBlock


!

columnsFrom:start to:stop do:aOneArgBlock
    "evaluate the argument, aOneArgBlock for the columns with index start to
     stop in the collection of column descriptors
    "
    columnDescriptors from:start to:stop do:aOneArgBlock


! !

!DSVColumnView methodsFor:'event handling'!

buttonMotion:buttonMask x:x y:y
    "mouse-move while button was pressed - handle multiple selection changes
    "
    |idx size scr p|

    dragAccessPoint notNil ifTrue:[
        dragIsActive ifFalse:[
            p := x @ y.
            (clickPosition dist:p) > 5.0 ifTrue:[ self startDragAt:p ]
        ].
        ^ self
    ].
    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 or:[self isInSelection:idx]]) ifTrue:[
        ^ self
    ].
    selectedRowIndex := selectedRowIndex asOrderedCollection.

    clickPosition notNil ifTrue:[
        (clickPosition - idx) abs > 1 ifTrue:[|s e|
            clickPosition < idx ifTrue:[
                s := clickPosition + 1.
                e := idx - 1.
            ] ifFalse:[
                s := idx + 1.
                e := clickPosition - 1.
            ].
            s to:e do:[:i|
                (self isInSelection:i) ifFalse:[
                    selectedRowIndex add:i.
                    self redrawRowAt:i colAt:0.
                ]
            ]
        ]
    ].
    selectedRowIndex add:(clickPosition := idx).

    scr == 0 ifTrue:[
        self redrawRowAt:idx colAt:0.
    ] ifFalse:[
        self scrollTo:(viewOrigin + (0 @ scr)) redraw:true
    ].
!

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
    ].
    self numberOfSelections == 1 ifTrue:[
        self firstIndexSelected == (self yVisibleToRowNr:y) ifTrue:[
            (     selectedColIndex == 0
              or:[selectedColIndex == (self xVisibleToColNr:x)]
            ) ifTrue:[
                self doubleClicked
            ]
        ]
    ]




!

buttonPress:button x:x y:y
    "a button was pressed - handle selection here
    "
    |rowNr colNr menu col sz view point|

    clickPosition   := nil.
    dragAccessPoint := nil.
    dragIsActive    := false.

    ((button == 2) or:[button == #menu]) ifTrue:[
        (menu := self findMenuForSelection) notNil ifTrue:[
            ^ menu startUp
        ]
    ] ifFalse:[
        (     (button == 1 or:[button == #select])
         and:[(rowNr := self yVisibleToRowNr:y) notNil
         and:[(colNr := self xVisibleToColNr:x) notNil]]
        ) 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 canDrag and:[self isSelected:rowNr inColumn:colNr]) ifTrue:[
                clickPosition   := x @ y.
                dragAccessPoint := (colNr @ rowNr).
            ] ifFalse:[
                self selectRowAt:rowNr colAt:colNr atPoint:(x @ y)
            ].
            ^ self
        ]
    ].
    super buttonPress:button x:x y:y



!

buttonRelease:button x:x y:y

    clickPosition notNil ifTrue:[
        dragAccessPoint notNil ifTrue:[
            dragIsActive ifFalse:[
                self selectRowAt:(dragAccessPoint y)
                           colAt:(dragAccessPoint x)
                         atPoint:clickPosition
            ].
            dragAccessPoint := nil.
            dragIsActive := false.
        ] ifFalse:[
            self selectionChanged
        ].        
        clickPosition := nil.
    ].
    super buttonRelease:button x:x y:y


!

characterPress:aChar x:x y:y
    "search row in column at x/y starting its printable label with cahracter.
    "
    |colNr rowNr lsize found column|

    (rowIfAbsentBlock notNil or:[(colNr := self xVisibleToColNr:x)]) isNil ifTrue:[
        ^ self
    ].
    rowNr  := self lastIndexSelected.
    lsize  := self size.
    column := self columnAt:colNr.
    found  := 0.

    lsize > rowNr ifTrue:[
     "/ search to end
        found := column findRowNrStartingWithChar:aChar start:(rowNr + 1) stop:lsize.
    ].

    (found == 0 and:[rowNr > 1]) ifTrue:[
     "/ search from begin
        found := column findRowNrStartingWithChar:aChar start:1 stop:(rowNr - 1)
    ].
    found ~~ 0 ifTrue:[
        self selectColIndex:colNr rowIndex:found.
    ].

!

contentsChanged
    "contents changed - move origin up if possible
    "
    |y|

    shown ifTrue:[
        self recomputeHeightOfContents.
        y := self maxViewOriginY.

        viewOrigin y > y ifTrue:[
            self scrollTo:(viewOrigin x @ y)
        ] ifFalse:[
            self updateEditViewOrigin.
        ]
    ].
    super contentsChanged


!

doubleClicked
    "handle a double click
    "
    |col sel idx|

    self hasSelection ifTrue:[
        idx := self firstIndexSelected.
        col := self selectedColumn.
        (col notNil and:[(sel := col doubleClickedSelector) notNil]) ifTrue:[
            (self at:idx) perform:sel
        ] ifFalse:[
            doubleClickActionBlock notNil ifTrue:[
                doubleClickActionBlock value:idx
            ]
        ]
    ]
!

findMenuForSelection
    "find the middle button menu for the current selection; returns the menu or nil
    "
    |col row menu|

    self numberOfSelections == 1 ifTrue:[
        row := self at:(self firstIndexSelected).
        col := self selectedColumn.

        (col notNil and:[(menu := col menuForRow:row) notNil]) ifTrue:[
            ^ menu
        ].
        col := columnDescriptors detect:[:c| c rendererType == #rowSelector]
                                 ifNone:[nil].

        col notNil ifTrue:[
            ^ col menuForRow:row
        ]
    ].
    ^ nil
!

keyPress:key x:x y:y
    "a key was pressed - handle page-keys here
    "
    <resource: #keyboard (#PreviousPage #NextPage #HalfPageUp #HalfPageDown
                          #BeginOfText #EndOfText #ScrollUp #ScrollDown
                          #CursorUp #CursorDown #CursorRight #CursorLeft)>

    |sensor n max idx col selRowNr|

    (key == #PreviousPage) ifTrue:[^ self pageUp].
    (key == #NextPage)     ifTrue:[^ self pageDown].
    (key == #HalfPageUp)   ifTrue:[^ self halfPageUp].
    (key == #HalfPageDown) ifTrue:[^ self halfPageDown].
    (key == #BeginOfText)  ifTrue:[^ self scrollToTop].
    (key == #EndOfText)    ifTrue:[^ self scrollToBottom].

    (key isCharacter)   ifTrue:[^ self characterPress:key x:x y:y ].

    sensor := self sensor.

    (key == #ScrollUp) ifTrue:[
        sensor isNil ifTrue:[
            n := 1
        ] ifFalse:[
            n := 1 + (sensor compressKeyPressEventsWithKey:#ScrollUp).
        ].
        ^ self scrollUp:(n * self verticalScrollStep)
    ].
    (key == #ScrollDown) ifTrue:[
        sensor isNil ifTrue:[
            n := 1
        ] ifFalse:[
            n := 1 + (sensor compressKeyPressEventsWithKey:#ScrollDown).
        ].
        ^ self scrollDown:(n * self verticalScrollStep)
    ].
    self numberOfSelections == 1 ifFalse:[^ self].
    selRowNr := self firstIndexSelected.

    key == #Return ifTrue:[
        ^ self doubleClicked
    ].
    max := self size.

    (key == #CursorUp or:[key == #CursorDown]) ifTrue:[
        sensor isNil ifTrue:[
            n := 1
        ] ifFalse:[
            n := 1 + (sensor compressKeyPressEventsWithKey:key).
        ].
        (n := n \\ max) == 0 ifTrue:[^ self ].

        key == #CursorUp ifTrue:[
            (n := selRowNr - n) <= 0  ifTrue:[n := max + n]
        ] ifFalse:[
            (n := selRowNr + n) > max ifTrue:[n := n - max]
        ].
        ^ self selectColIndex:selectedColIndex rowIndex:n.
    ].

    selectedColIndex == 0 ifTrue:[  "/ line is selected
        ^ self
    ].

    (key == #CursorRight or:[key == #CursorLeft]) ifTrue:[
        sensor isNil ifTrue:[
            n := 1
        ] ifFalse:[
            n := 1 + (sensor compressKeyPressEventsWithKey:key).
        ].
        idx := selectedColIndex.
        max := self numberOfColumns.

        key == #CursorLeft ifTrue:[
            [n ~~ 0] whileTrue:[
                (idx := idx - 1) == 0 ifTrue:[idx := max].
                ((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:selRowNr) ifTrue:[n := n - 1]
            ]
        ].

        ^ self selectColIndex:idx rowIndex:selRowNr.
    ].




!

originChanged:delta
    "this one is sent, after the origin of my contents has changed -
     tell dependents (i.e. scrollers) about this
    "
    super originChanged:delta.
    self updateEditViewOrigin.
!

sizeChanged:how
    "size changed - move origin up if possible
    "
    super sizeChanged:how.

    (shown and:[self numberOfColumns ~~ 0 and:[self fitColumns not]]) ifTrue:[
        self scrollTo:viewOrigin.       "/ validates viewOrigin
        self invalidate.
        self scrollToSelection
    ]

! !

!DSVColumnView methodsFor:'gc operations'!

registerImage:anImage key:aKey
    "any row can register an image with a unique identifier a key symbol
    "
    |img|

    (img := registererImages at:aKey ifAbsent:nil) notNil ifTrue:[
        ^ img
    ].
    img := anImage onDevice:device.
    img clearMaskedPixels.
    registererImages at:aKey put:img.
    ^ img
!

registeredImageAt:aKey
    "any row can register an image with a unique identifier
    "
    ^ registererImages at:aKey ifAbsent:nil
!

releaseAllRegisteredImages
    "release all registered images
    "
    registererImages := IdentityDictionary new.
! !

!DSVColumnView methodsFor:'initialization'!

create
    "set color on device
    "
    super create.
    fgColor     := fgColor     on:device.
    bgColor     := bgColor     on:device.
    hgLgFgColor := hgLgFgColor on:device.
    hgLgBgColor := hgLgBgColor on:device.

    buttonShadowColor := buttonShadowColor on:device.
    buttonLightColor  := buttonLightColor on:device.

    buttonHalfShadowColor notNil ifTrue:[
        buttonHalfShadowColor := buttonHalfShadowColor on:device
    ].

    buttonHalfLightColor notNil ifTrue:[
        buttonHalfLightColor := buttonHalfLightColor on:device
    ].
!

destroy
    "remove dependencies
    "
    self columnHolder:nil.
    self beDependentOfRows:false.
    super destroy
!

initStyle
    "setup colors
    "
    |v b|

    super initStyle.

    DefaultForegroundColor isNil ifTrue:[
        self class updateStyleCache
    ].
    fgColor     := DefaultForegroundColor.
    bgColor     := DefaultBackgroundColor.
    hgLgFgColor := DefaultHilightForegroundColor.
    hgLgBgColor := DefaultHilightBackgroundColor.

    shadowColor isNil ifTrue:[
        shadowColor := Color grayPercent:40.
    ].

    lightColor isNil ifTrue:[
        lightColor := Color grayPercent:75
    ].

    buttonLightColor    := ButtonLightColor  ? lightColor.
    buttonShadowColor   := ButtonShadowColor ? shadowColor.

    (ButtonEdgeStyle == #soft) ifTrue:[
        buttonHalfShadowColor := ButtonHalfShadowColor.
        buttonHalfLightColor  := ButtonHalfLightColor.

        buttonHalfShadowColor isNil ifTrue:[
            buttonHalfShadowColor := buttonShadowColor lightened
        ]
    ].

    v := ComboBoxView new.
    b := v menuButton.

    (comboButtonForm := b label) isImage ifTrue:[
        comboButtonForm clearMaskedPixels
    ].

    comboButtonLevel  := b offLevel.
    comboButtonExtent := (b preferredExtent x) @ (v preferredExtent y).

    b := CheckToggle new.

    (checkToggleForm := CheckToggle checkFormOn:device) isImage ifTrue:[
        checkToggleForm clearMaskedPixels
    ].
    checkToggleLevel  := b offLevel.
    checkToggleExtent := b preferredExtent.












!

initialize
    "set default attributes
    "
    super initialize.

    viewOrigin        := 0@0.
    font              := font on:device.
    rowHeight         := font height.
    multipleSelectOk  := false.
    selectedRowIndex  := selectedColIndex  := 0.
    registererImages  := IdentityDictionary new.
    separatorSize     := 1.
    columnDescriptors := #().
    beDependentOfRows := false.
    verticalSpacing   := self class verticalSpacing.
    horizontalSpacing := self class horizontalSpacing.
    colorMap          := Dictionary new.
    catchChangeEvents := false.
    dragIsActive      := false.

    self lineWidth:0.
!

mapped
    "set selection if exists after mapping
    "
    |idx|

    super mapped.

    idx := self firstIndexSelected.

    idx ~~ 0 ifTrue:[
        self scrollToRowAt:idx colAt:0.        
    ].
!

realize
    "recompute contents and fit columns to view
    "
    self  bitGravity:#NorthWest.
    self  recomputeHeightOfContents.
    super realize.
    self  fitColumns.
! !

!DSVColumnView methodsFor:'obsolete'!

has3Dsepartors
    "shouldn't be used any more
    "
    ^ self has3Dseparators
!

has3Dsepartors:aBool
    "shouldn't be used any more
    "
    self has3Dseparators:aBool

! !

!DSVColumnView methodsFor:'private'!

detectViewAt:aPoint in:aView
    |p|

    (aView notNil and:[aView subViews notNil]) ifTrue:[
        aView subViews do:[:sv|
            p := device translatePoint:aPoint from:(self id) to:(sv id).

            (p x >= 0 and:[p y >= 0 and:[p x <= sv width and:[p y <= sv height]]]) ifTrue:[
                ^ self detectViewAt:aPoint in:sv
            ]
        ]
    ].
    ^ aView
!

fitColumns
    "fit columns to view
    "
    |raiseNotify lastColumn dX sz expand resizables deltaWidth|

    self canFit ifFalse:[^ false ].

    resizables  := 0.
    deltaWidth  := 0.

    preferredExtent isNil ifTrue:[
        raiseNotify := catchChangeEvents.
        catchChangeEvents := true.
        self preferredExtent.
        catchChangeEvents := raiseNotify.
        raiseNotify := raiseNotify not.
    ] ifFalse:[
        raiseNotify := false
    ].

    self columnsDo:[:aCol|
        aCol canResize ifTrue:[
            resizables := resizables + 1.
            deltaWidth := aCol setMinWidth.
            lastColumn := aCol.
        ]
    ].

    resizables == 0 ifFalse:[
        sz := self widthOfContents.

        (expand := sz < width) ifTrue:[
            deltaWidth := width - sz + margin + margin
        ]
    ].

    deltaWidth == 0 ifTrue:[
        raiseNotify ifTrue:[ self changed:#columnsLayout ].
        ^ false
    ].

    expand ifTrue:[
        (dX := deltaWidth // resizables) ~~ 0 ifTrue:[
            self columnsDo:[:aCol|aCol canResize ifTrue:[aCol growWidth:dX]]
        ].
        lastColumn growWidth:(deltaWidth - (dX * resizables)).
    ].

    self preferredExtentChanged.

    shown ifTrue:[
        self invalidate.

        self hasSelection ifTrue:[
            editView notNil ifTrue:[
                editView width:(self selectedColumn width - separatorSize)
            ].
            self scrollToSelection.
        ].
        self contentsChanged.
    ].

    self changed:#columnsLayout.
  ^ true.


!

maxViewOriginY
    "returns the maximum possible y of the view origin
    "
    |y|

    y := self heightOfContents - self innerHeight.
  ^ y max:0

!

updateEditViewOrigin
    "update origin of the editView
    "
    |x y|

    editView notNil ifTrue:[
        y := self yVisibleOfRowNr:(self firstIndexSelected).
        x := self xVisibleOfColNr:(self selectedColIndex).

        editView origin:(x @ y).
    ].

!

xVisibleOfColNr:aColNr
    "returns visible x assigned to a column number
    "
    |x|

    x := margin - viewOrigin x.
    self columnsFrom:1 to:(aColNr - 1) do:[:aCol| x := x + aCol width ].
  ^ x

!

xVisibleToColNr:x
    "returns the column number assigned to a physical x or nil
    "
    |x0 nr|

    x0 := x + viewOrigin x - margin.
    nr := 1.

    self columnsDo:[:aCol|
        (x0 := x0 - aCol width) <= 0 ifTrue:[^ nr].
        nr := nr + 1.
    ].
    ^ nil.

!

yVisibleOfRowNr:aRowNr
    "returns visible y assigned to the row number
    "
    ^ (aRowNr - 1) * rowHeight + margin - viewOrigin y

!

yVisibleToRowNr:y
    "returns the row number assigned to a physical y or nil
    "
    |y0|

    y0 := (y + viewOrigin y - margin) // rowHeight + 1.
  ^ (y0 <= self size) ifTrue:[y0] ifFalse:[nil]

! !

!DSVColumnView methodsFor:'queries'!

canFit
    "returns true if columns can be fit to view
    "
    ^ canFit
!

indexOfFirstRowShown
    "returns index of first row shown
    "
    |idx|

    idx := (self yOriginOfContents // rowHeight) + 1.
  ^ (idx <= self size) ifTrue:[idx] ifFalse:[0]

!

numberOfColumns
    "returns number of columns
    "
    ^ columnDescriptors size

!

numberOfRows
    "returns number of raws
    "
    ^ self size

!

rowHeight
    "get the height of the highest row in pixels
    "
    ^ rowHeight

!

separatorSize
    "returns vertical/horizontal size of a separator dependent on the
     3D effect.
    "
    ^ separatorSize

!

size
    "returns number of raws
    "
    ^ list size

! !

!DSVColumnView methodsFor:'recomputation'!

hasPreferredExtent
    "returns true if preferred extent is accumulated
    "
    ^ preferredExtent notNil
!

preferredExtent
    "recompute preferred extent; raise notification
    "
    |x|

    preferredExtent notNil ifTrue:[
        ^ preferredExtent
    ].
    x := 3.
    rowHeight := 0.

    self columnsDo:[:aCol|
        rowHeight := (aCol heightOfHighestRow) max:rowHeight.
        x := x + (aCol minWidth).
    ].
    rowHeight := (rowHeight + separatorSize + verticalSpacing + verticalSpacing + 1) // 2 * 2.
    preferredExtent := (x + margin + margin) @ (self size * rowHeight).

    x := (rowHeight - separatorSize - font height) // 2 + font ascent.
    self columnsDo:[:aCol|aCol textInsetChanged:x].
    self changed:#columnsLayout.
  ^ preferredExtent


!

preferredExtentChanged
    |y x|

    y := viewOrigin y.
    x := viewOrigin x.

    (y ~~ 0 or:[x ~~ 0]) ifTrue:[
        self originWillChange.
        viewOrigin := 0 @ 0.
        preferredExtent := nil.
        self originChanged:(x negated  @ y negated).
    ]
!

recomputeHeightOfContents

    preferredExtent notNil ifTrue:[
        preferredExtent y:(rowHeight * self size)
    ] ifFalse:[
        self preferredExtent
    ].
! !

!DSVColumnView methodsFor:'scroller interface'!

heightOfContents
    "return the height of the contents in pixels
    "
    ^ self preferredExtent y


!

innerHeight
    "returns the inner height of the contents shown
    "
    ^ height - margin - margin

!

innerWidth
    "returns the inner width of the contents shown
    "
    ^ width - margin - margin

!

verticalScrollStep
    "return the amount to scroll when stepping up/down.
    "
    ^ rowHeight



!

viewOrigin
    "return the viewOrigin; thats the coordinate of the contents 
     which is shown topLeft in the view.
    "
    ^ viewOrigin

!

widthOfContents
    "return the width of the contents in pixels
    "
    preferredExtent isNil ifTrue:[
        self preferredExtent
    ].
    ^ preferredExtent x

!

xOriginOfContents
    "return the horizontal origin of the contents in pixels
    "
    ^ viewOrigin x 

!

yOriginOfContents
    "return the vertical origin of the contents in pixels
    "
    ^ viewOrigin y

! !

!DSVColumnView methodsFor:'scrolling'!

halfPageDown
    "scroll down half a page
    "
    self scrollDown:(self innerHeight // 2)


!

halfPageUp
    "scroll up half a page
    "
    self scrollUp:(self innerHeight // 2)

!

scrollTo:anOrigin redraw:doRedraw
    "change origin to have newOrigin be visible at the top-left.
    "
    |x y dX dY newOrg dltOrg h innerWT innerHG|

    shown ifFalse:[
        ^ self
    ].

    [self sensor hasExposeEventFor:nil] whileTrue:[
        self windowGroup processExposeEvents
    ].

    innerWT := self innerWidth.
    innerHG := self innerHeight.

    h := viewOrigin y.

    (y := anOrigin y) > h ifTrue:[              "/ end of contents
        y > (dY := self maxViewOriginY) ifTrue:[
            y := dY max:h
        ]
    ] ifFalse:[
        y := y max:0.
    ].

    (x := anOrigin x) > 0 ifTrue:[
        x := x min:(self widthOfContents - innerWT).
    ].
    x      := x max:0.
    newOrg := (x @ y).
    dltOrg := newOrg - viewOrigin.
    dX     := dltOrg x.
    dY     := dltOrg y.

    (dX == 0 and:[dY == 0]) ifTrue:[
        ^ self
    ].
    self originWillChange.
    viewOrigin := newOrg.

    doRedraw ifFalse:[
        ^ self originChanged:dltOrg
    ].

    dY ~~ 0 ifTrue:[                            "/ SCROLL VERTICAL
        dY := dY abs.

        (dX ~~ 0 or:[innerHG - dY < 20]) ifTrue:[
            self redraw.
        ] ifFalse:[                             "/ COPY VERTICAL
            |y0 y1|

            y0 := y1 := margin + dY.
            h  := innerHG - dY.

            dltOrg y < 0 ifTrue:[y0 := margin. y := y0]
                        ifFalse:[y1 := margin. y := y1 + h].

            self catchExpose.
            self copyFrom:self x:margin y:y0 toX:margin y:y1 width:innerWT height:h async:true.
            self waitForExpose.
            self redrawX:margin y:y width:innerWT height:(innerHG - h).
        ]
    ] ifFalse:[                                 "/ SCROLL HORIZONTAL
        dX := dX abs.

        innerWT - dX < 20 ifTrue:[
            self redraw.
        ] ifFalse:[                             "/ COPY HORIZONTAL
            |x0 x1 w|

            x0 := x1 := dX + margin.
            w  := width - dX - margin.

            dltOrg x < 0 ifTrue:[x0 := x := margin ]
                        ifFalse:[x1 := margin. x := w].

            self catchExpose.
            self copyFrom:self x:x0 y:margin toX:x1 y:margin width:w height:innerHG async:true.
            self waitForExpose.
            self redrawX:x y:margin width:(width - w) height:innerHG.
        ]
    ].
    self originChanged:dltOrg.
!

scrollToRowAt:aRowNr colAt:aColNr
    "make row at a row number in column at a column number visible
    "
    |x y l dY dX|

    (    (aRowNr between:1 and:(self size))
     and:[aColNr between:0 and:(self numberOfColumns)]
    ) ifFalse:[
        ^ self
    ].

    dY := dX := 0.
    y  := self yVisibleOfRowNr:aRowNr.

    y < margin ifTrue:[
        dY := margin - y.
    ] ifFalse:[
        y := y + rowHeight.
        l := height - margin.
        y > l ifTrue:[dY := l - y]
    ].

    aColNr == 0 ifTrue:[
        dY == 0 ifTrue:[^ self].
        dX := 0.
    ] ifFalse:[
        x  := self xVisibleOfColNr:aColNr.

        x < margin ifTrue:[
            dX := margin - x
        ] ifFalse:[
            x := x + (self columnAt:aColNr) width.
            l := width - margin.
            x > l ifTrue:[dX := l - x]
        ]
    ].

    (dX == 0 and:[dY == 0]) ifFalse:[
        self scrollTo:(viewOrigin - (dX @ dY)).
    ]


!

scrollToSelection
    "make selection visible
    "
    |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 row selected or 0
    "
    multipleSelectOk ifFalse:[
        ^ selectedRowIndex
    ].
    selectedRowIndex size ~~ 0 ifTrue:[
        ^ selectedRowIndex at:1
    ].
    ^ 0
!

hasSelection
    "returns true if a selection exists
    "
    ^ self numberOfSelections ~~ 0


!

isInSelection:aRowNr
    "return true, if row, aRowNr is in the selection
    "
    aRowNr ~~ 0 ifTrue:[
        multipleSelectOk ifFalse:[
            ^ aRowNr == selectedRowIndex
        ].
        selectedRowIndex size ~~ 0 ifTrue:[
            ^ selectedRowIndex includes:aRowNr
        ]
    ].
    ^ false
!

isRowSelected:aRowNr
    "return true, if row is in the selection
    "
    selectedColIndex == 0 ifTrue:[
        ^ self isInSelection:aRowNr
    ].
    ^ false
!

isSelected:aRowNr inColumn:aColNr
    "returns true if cell in a row; a row number, in a column, a column
     number is selected.
    "
    (self isInSelection:aRowNr) ifTrue:[
        ^ (selectedColIndex == 0 or:[selectedColIndex == aColNr])
    ].
    ^ false
!

lastIndexSelected
    "returns index of last row selected or 0
    "
    multipleSelectOk ifFalse:[
        ^ selectedRowIndex
    ].
    selectedRowIndex size ~~ 0 ifTrue:[
        ^ selectedRowIndex last
    ].
    ^ 0
!

numberOfSelections
    "return the number of selected rows
    "
    multipleSelectOk ifFalse:[
        ^ selectedRowIndex ~~ 0 ifTrue:[1] ifFalse:[0]
    ].
    ^ selectedRowIndex size
!

selectColIndex:aColNr rowIndex:aRowNr
    "change selection with notification
    "
    |oC oR|

    oC := self selectedColIndex.
    oR := self selectedRowIndex.

    self setSelectColIndex:aColNr rowIndex:aRowNr.

    (oC ~~ self selectedColIndex or:[oR ~= self selectedRowIndex]) ifTrue:[
        self selectionChanged
    ].
!

selectRow:something
    "select a row
    "
    ^ self selectedRowIndex:something
!

selectRowAt:rowNr colAt:colNr atPoint:aPoint
    |v p|

    self selectColIndex:colNr rowIndex:rowNr.

    (v := self detectViewAt:aPoint in:editView) notNil ifTrue:[
        p := device translatePoint:aPoint from:(self id) to:(v id).

        self sensor pushEvent:(WindowEvent buttonEvent
                                 for:v
                                 type:#buttonPress:x:y:
                                 arguments:(Array with:#select with:p x with:p y)
                              )
    ].


!

selectRowIndex:something
    "set selection of rows
    "
    self selectColIndex:selectedColIndex rowIndex:something


!

selectedColIndex
    "returns selected column number or 0
    "
    ^ selectedColIndex
!

selectedColumn
    "returns selected column or nil
    "
    ^ columnDescriptors at:selectedColIndex ifAbsent:nil.
!

selectedRow
    "returns selected row (or collection if multiple selection) or 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
    "returns selected row number or 0
    "
    ^ selectedRowIndex
!

selectedRowIndex:something
    "set selection of rows
    "
    self selectColIndex:selectedColIndex rowIndex:something


!

selectionChanged
    "selection has changed
    "
    self changed:#selection.

    actionBlock notNil ifTrue:[
        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
    "
    |editSpec rowNr colNr newCol oldCol oldRow sensor sglSelRow index oldSz|

    rowNr := self validateSelection:aRowNr.

    multipleSelectOk ifTrue:[
        colNr := (rowNr size == 1) ifTrue:[aColNr] ifFalse:[0]
    ] ifFalse:[
        colNr := rowNr ~~ 0 ifTrue:[aColNr] ifFalse:[0]
    ].

    (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
    ].

    "/ release old selection

    oldSz  := self numberOfSelections.
    oldCol := selectedColIndex.
    oldRow := selectedRowIndex.

    selectedRowIndex := rowNr.
    selectedColIndex := colNr.

    oldSz == 1 ifTrue:[
        multipleSelectOk ifTrue:[oldRow := oldRow at:1].

        editValue notNil ifTrue:[
            editValue removeDependent:self.
            (self columnAt:oldCol) at:oldRow put:editValue value.
            editValue := nil
        ].
        editView notNil ifTrue:[
            editView destroy.
            editView := nil.
        ]
    ].
    shown ifFalse:[^ self ].

    oldSz > 1 ifTrue:[                                  "/ redraw old selection
        oldRow do:[:aRowNr|                             "/ unselected if visible
            self redrawRowAt:aRowNr colAt:0
        ]
    ] ifFalse:[
        oldSz == 1 ifTrue:[
            self redrawRowAt:oldRow colAt:oldCol
        ]
    ].   

    "/ show new selection

    newCol notNil ifTrue:[
        self scrollToRowAt:sglSelRow colAt:colNr.
        editSpec := newCol editorAt:sglSelRow.

        editSpec notNil ifTrue:[
            editView := SimpleView extent:(  (newCol width - separatorSize) 
                                           @ (rowHeight    - separatorSize)
                                          )
                                       in:self.
            self updateEditViewOrigin.
            editView viewBackground:hgLgBgColor.
            editView add:(editSpec at:1).

            (editValue := (editSpec at:2)) notNil ifTrue:[
                editValue addDependent:self.
            ].
            editView realize.
        ] ifFalse:[
            self redrawRowAt:sglSelRow colAt:colNr
        ].
    ] ifFalse:[
        self selectionIndicesDo:[:i| self redrawRowAt:i colAt:0 ].
        self scrollToRowAt:(self firstIndexSelected) colAt:0
    ].

    sensor := self sensor.                              "/ catch expose events

    [sensor hasExposeEventFor:nil] whileTrue:[
        self windowGroup processExposeEvents
    ].


!

validateSelection:aSelection
    |newSel|

    newSel := aSelection.

    (self 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 := self identityIndexOfRow:aSelection
    ] ifTrue:[
        newSel := nil.

        aSelection size ~~ 0 ifTrue:[
            aSelection first isNumber ifTrue:[
                newSel := aSelection
            ] ifFalse:[
                aSelection do:[:el||n|
                    (n := self identityIndexOfRow: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.34 1998-04-16 11:00:21 ca Exp $'
! !