DataSetColumn.st
author ca
Wed, 20 May 1998 09:38:03 +0200
changeset 891 f4d2ed9d3b88
parent 883 0a790ad56286
child 991 c1bc86ebe79e
permissions -rw-r--r--
checkin from browser

"
 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.
"




Object subclass:#DataSetColumn
	instanceVariableNames:'columnNumber dataSet labelExtent minWidth width description form
		buttonInset buttonExtent textInset drawableAction toggleExtent
		rendererType backgroundColor foregroundColor fgSelector
		bgSelector columnAlignment label'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-DataSet'
!

!DataSetColumn 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
"
    represent one single column description of a DataSetView

    [Instance variables:]

        columnNumber    <Integer>               sequence number (into list of columns)
        description     <DataSetColumnSpec>     the column description
        dataSet         <DSVColumnView>         the view it belongs to
        width           <Integer>               width of column
        minWidth        <Integer>               minimum required width by the column
        buttonInset     <Integer>               top inset of a button (toggle)
        buttonExtent    <Point>                 extent of form
        textInset       <Integer>               top inset of a string
        form            <Form>                  a form drawn in the cell
        labelExtent     <Point>                 the preferred extent of the cell label on device
        drawableAction  <Action>                action to access the printable
                                                label of a cell
        rendererType    <Type>                  renderer type derived from
                                                column specification.
        backgroundColor <Color or nil>          background color of all cells or nil
                                                (nil: use default background color).
        foregroundColor <Color or nil>          foreground color of all cells or nil
                                                (nil: use default foreground color).
        fgSelector      <Selector or nil>       access specific foreground color for
                                                a cell
        bgSelector      <Selector or nil>       access specific background color for
                                                a cell


    [author:]
        Claus Atzkern

    [see also:]
        DataSetColumnSpec
        DSVColumnView
        DataSetView
"


! !

!DataSetColumn methodsFor:'accessing'!

at:aRowNr
    "get the value of the raw at an index, aRowNr
    "
    ^ description row:(dataSet at:aRowNr) at:columnNumber
!

at:aRowNr put:something
    "set the value of the raw at an index, aRowNr
    "
    description row:(dataSet at:aRowNr) at:columnNumber put:something
!

backgroundColor
    ^ backgroundColor
!

description
    "returns the column description
    "
    ^ description


!

foregroundColor
    ^ foregroundColor
!

label
    "get the label assigned to the column
    "
    ^ label


!

rendererType
    "returns my renderer type
    "
    ^ rendererType
!

width
    "returns the width in pixels
    "
    |end|

    width notNil ifTrue:[ ^ width ].                            "/ already computed

    (    (width := description width)    ~~ 0                   "/ fixed size
     or:[(width := description minWidth) ~~ 0]                  "/ start size
    ) ifFalse:[
        self containsText ifTrue:[
            "/ take maximum 10 entries to calculate the width;
            "/ can be resized later if neccessary

            end := 10 min:dataSet size.

            1 to:end do:[:aRowNr||lbl|
                lbl := self drawableAt:aRowNr.

                (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)
            ].
        ].
        width := (width + buttonExtent x) max:(4 + labelExtent x)
    ].
    ^ width := minWidth := width + dataSet separatorSize + (2 * dataSet horizontalSpacing).
!

width:aWidth
    "set the width
    "
    |w|

    (w := description width) ~~ 0 ifTrue:[             "/ fixed size
        width := minWidth := w
    ] ifFalse:[
        width := aWidth max:minWidth
    ].

! !

!DataSetColumn methodsFor:'drawing'!

drawButtonAtIndex:anIndex x:xR y:yR with:fgColor and:bgColor
    |y0 x0 extent lv w h|

    w := buttonExtent x.

    rendererType ~~ #CheckToggle ifTrue:[
        (self hasChoices:anIndex) ifFalse:[
            ^ self
        ].
        lv := dataSet comboButtonLevel.
        x0 := width - w - 4
    ] ifFalse:[
        lv := dataSet checkToggleLevel.
        x0 := width - w - (dataSet separatorSize) + 1 // 2        
    ].

    y0 := yR + buttonInset.
    x0 := xR + x0.

    dataSet drawEdgesAtX:x0 y:y0 width:w height:(buttonExtent y) level:lv.

    (rendererType ~~ #CheckToggle or:[self at:anIndex]) ifTrue:[
        (dataSet isRowSelected:anIndex) ifFalse:[dataSet paint:fgColor on:bgColor]
                                         ifTrue:[dataSet paint:(dataSet hgLgFgColor)
                                                            on:(dataSet hgLgBgColor)
                                                ].
        extent := (buttonExtent - form extent) // 2.
        dataSet displayImage:form x:(x0 + extent x) y:(y0 + extent y)
    ].
!

drawFrom:start times:nTimes x0:x0 yTop:yTop yBot:yBot with:fgColor and:bgColor
    "redraw rows between start and stop
    "
    |lgCol dkCol fg bg lblFg lblBg lbl row colSp fH fW fE sepSz level
     h  "{ Class:SmallInteger }"
     n  "{ Class:SmallInteger }"
     y  "{ Class:SmallInteger }"
     x  "{ Class:SmallInteger }"
     xI "{ Class:SmallInteger }"
     xCol "{ Class:SmallInteger }"
     spacing "{ Class:SmallInteger }"|

    h  := dataSet rowHeight.

    (bg := backgroundColor) isNil ifTrue:[
        bg := bgColor
    ] ifFalse:[
        dataSet paint:(dataSet colorOnDevice:bg).
        dataSet fillRectangleX:x0 y:yTop width:width  height:(yBot - yTop - 1)
    ].
    fg    := foregroundColor ? fgColor.
    lgCol := dataSet hgLgFgColor.
    dkCol := dataSet hgLgBgColor.
    sepSz := dataSet separatorSize.
    spacing := dataSet horizontalSpacing.
    y     := yTop + textInset.
    x     := x0   + spacing.
    n     := start.

    nTimes timesRepeat:[
        row := dataSet at:n.
        lbl := drawableAction value:row.

        (dataSet isSelected:n inColumn:columnNumber) ifTrue:[
            dataSet paint:dkCol.
            dataSet fillRectangleX:x0 y:y - textInset width:width height:(h - 2).

            rendererType == #rowSelector ifTrue:[
                lbl := form
            ] ifFalse:[
                lbl isText ifTrue:[lbl := lbl string]
            ].
            lblBg := dkCol.
            lblFg := lgCol.
        ] ifFalse:[
            (bgSelector notNil and:[(lblBg := row perform:bgSelector) notNil]) ifTrue:[
                dataSet paint:(lblBg := dataSet colorOnDevice:lblBg).
                dataSet fillRectangleX:x0 y:y - textInset width:width height:(h - 2).                
            ] ifFalse:[
                lblBg := bg
            ].
            lbl notNil ifTrue:[
                (fgSelector notNil and:[(lblFg := row perform:fgSelector) notNil]) ifFalse:[
                    lblFg := fg.
                ] ifTrue:[
                    lblFg := dataSet colorOnDevice:lblFg.
                ].
            ]
        ].
        lbl notNil ifTrue:[
            columnAlignment == #left ifTrue:[
                xCol := x
            ] ifFalse:[
                xCol := width - (lbl widthOn:dataSet).

                columnAlignment == #right ifTrue:[xCol := xCol - spacing]
                                         ifFalse:[xCol := xCol // 2].

                xCol := (x0 + xCol) max:0.
            ].
            dataSet paint:lblFg on:lblBg.
            lbl displayOn:dataSet x:xCol y:y
        ].
        y := y + h.
        n := n + 1.
    ].

    (form notNil and:[rendererType ~~ #rowSelector]) ifTrue:[
        y := yTop.
        n := start.

        nTimes timesRepeat:[
            self drawButtonAtIndex:n x:x0 y:y with:fgColor and:bgColor.
            y := y + h.
            n := n + 1.
        ].
    ].

    "/ DRAW SEPARATORS

    x  := x0 + width - 1.

    sepSz == 1 ifTrue:[
        y := yTop.

        dataSet paint:fgColor.

        description showColSeparator ifTrue:[
            dataSet displayLineFromX:x y:yTop toX:x y:yBot - 1
        ].

        description showRowSeparator ifTrue:[
            y := yTop - 1.

            nTimes timesRepeat:[
                y := y + h.
                dataSet displayLineFromX:x0 y:y toX:x y:y
            ]
        ]
    ] ifFalse:[
        dkCol := dataSet separatorDarkColor.
        lgCol := dataSet separatorLightColor.

        (colSp := description showColSeparator) ifTrue:[
            y := yBot - 1.
            dataSet paint:lgCol.
            dataSet displayLineFromX:x y:yTop toX:x y:y.
            x := x - 1.
            dataSet paint:dkCol.
            dataSet displayLineFromX:x y:yTop toX:x y:y.
        ] ifFalse:[
            dataSet paint:dkCol
        ].

        description showRowSeparator ifTrue:[
            y := yTop - 2.
            x := x0 + width.

            colSp ifTrue:[x := x - 2].

            nTimes timesRepeat:[
                y := y + h.
                dataSet displayLineFromX:x0 y:y toX:x y:y.
            ].
            y := yTop - 1.
            dataSet paint:lgCol.

            nTimes timesRepeat:[
                y := y + h.
                dataSet displayLineFromX:x0 y:y toX:x y:y.
            ]
        ]
    ]

!

invalidate
    "set to invalidate; forces a recomputation
    "
    minWidth := width := nil.

! !

!DataSetColumn methodsFor:'editing'!

editorAt:aRowNr
    |val row|

    row := dataSet at:aRowNr.
    val := description row:row at:columnNumber.

    val isText ifTrue:[val := val string].

    ^ description editorOn:row value:val.
! !

!DataSetColumn methodsFor:'event handling'!

doesNotUnderstand:aMessage

    (description respondsTo:(aMessage selector)) ifTrue:[
        ^ aMessage sendTo:description
    ].
    ^ super doesNotUnderstand:aMessage

!

textInsetChanged:aTextInset
    "recompute all attributes
    "
    |lbl|

    self containsText ifTrue:[
        textInset := dataSet verticalSpacing.

        dataSet size ~~ 0 ifTrue:[
            lbl := self drawableAt:1.

            (lbl isString or:[lbl isNumber]) ifTrue:[
                textInset := aTextInset
            ] ifFalse:[
                (lbl isNil and:[description printSelector isNil]) ifTrue:[
                    textInset := aTextInset.
                ]
            ]
        ]
    ] ifFalse:[
        textInset := (  (dataSet rowHeight)
                      - (form height)
                      - (dataSet separatorSize)
                     ) // 2.    
    ].    

    form isNil ifTrue:[
        buttonInset := 0
    ] ifFalse:[        
        buttonInset := (  (dataSet rowHeight)
                        - (buttonExtent x)
                        - (dataSet separatorSize)
                       ) // 2.

        rendererType == #CheckToggle ifTrue:[
            buttonInset := buttonInset + 1
        ]        
    ].


! !

!DataSetColumn methodsFor:'grow & degrow'!

growWidth:n
    "grow the width for n pixels
    "
    width := width + n.


!

minWidth
    "get my minimum width required by the entries into the column
    "
    ^ minWidth notNil ifTrue:[minWidth] ifFalse:[self width]


!

setMinWidth
    "set the width to the required width. returns the psitive delta width
    "
    |deltaX|

    deltaX := width - minWidth.
    width  := minWidth.
  ^ deltaX.


! !

!DataSetColumn methodsFor:'initialization'!

on:aDSVColumnView description:aDescription columnNumber:aNumber
    "instance creation; set attributes dependent on the description
    "
    |device selector format idx type oldFont newFont|

    columnNumber    := aNumber.
    dataSet         := aDSVColumnView.
    description     := aDescription.
    rendererType    := description rendererType.
    form            := width := nil.
    device          := dataSet device.
    drawableAction  := [:aRow| nil ].
    fgSelector      := description foregroundSelector.
    bgSelector      := description backgroundSelector.
    backgroundColor := description backgroundColor.
    foregroundColor := description foregroundColor.
    buttonExtent    := 0 @ 0.
    labelExtent     := 0 @ 0.
    columnAlignment := #left.

    backgroundColor notNil ifTrue:[
        backgroundColor := backgroundColor on:dataSet device
    ].
    foregroundColor notNil ifTrue:[
        foregroundColor := foregroundColor on:dataSet device
    ].

    oldFont := nil.
    label   := self resolveLabelWithBuilder:(dataSet builder).

    (label respondsTo:#string) ifTrue:[
        "/
        "/ must set the font to accumulate the real extent of a string label
        "/
        (label isString and:[label isEmpty]) ifTrue:[
            label := nil
        ] ifFalse:[
            (newFont := description labelFont) notNil ifTrue:[
                oldFont := dataSet font.
                dataSet font:newFont.
            ]
        ]
    ].

    label notNil ifTrue:[
        labelExtent := Point x:(label widthOn:dataSet) y:(label heightOn:dataSet).
    ].

    oldFont notNil ifTrue:[
        dataSet font:oldFont
    ].

    rendererType == #CheckToggle ifTrue:[
        form := dataSet checkToggleForm.
        buttonExtent := dataSet checkToggleExtent.
      ^ self
    ].

    rendererType == #rowSelector ifTrue:[
        form  := dataSet rowSelectorForm.
        buttonExtent := dataSet rowSelectorExtent.
      ^ self
    ].

    (rendererType == #ComboBox or:[rendererType == #ComboList]) ifTrue:[
        form := dataSet comboButtonForm.
        buttonExtent := dataSet comboButtonExtent.
    ] ifFalse:[
        columnAlignment := description columnAlignment
    ].

    selector := description printSelector.

    selector notNil ifTrue:[
        drawableAction := [:aRow| aRow perform:selector with:dataSet ].
        ^ self
    ].

    (     (format := description formatString) notNil
     and:[(type   := description type) == #number or:[type == #numberOrNil]]
    ) ifTrue:[
        "/ has a format string for number (supports only floats)

        (idx := format indexOf:$.) ~~ 0 ifTrue:[
            idx := format size - idx
        ].
        format := '%0.', idx printString, 'f'.

        drawableAction := [:aRow||n|
            n := description row:aRow at:columnNumber.
            n isReal ifTrue:[n := n asFloat printfPrintString:format].
            n
        ]
    ] ifFalse:[         "/ default: no format string
        drawableAction := [:aRow| description row:aRow at:columnNumber ]
    ]


!

resolveLabelInBuilder:aBuilder
    |label appl|

    aBuilder isNil ifTrue:[
        ^ description rawLabel        
    ].

    (label := description label) isString ifTrue:[
        description labelIsImage ifTrue:[
            aBuilder isEditing ifTrue:[
                label := nil
            ] ifFalse:[
                label := aBuilder labelFor:(label asSymbol)
            ].
            ^ label ? description class defaultIcon
        ].
        description translateLabel == true ifTrue:[
            (appl := aBuilder application) notNil ifTrue:[
                ^ (appl resources string:label) ? label
            ]
        ]
    ].
    ^ label
!

resolveLabelWithBuilder:aBuilder
    |label appl|

    aBuilder isNil ifTrue:[
        ^ description rawLabel        
    ].

    (label := description label) isString ifTrue:[
        description labelIsImage ifTrue:[
            aBuilder isEditing ifTrue:[
                label := nil
            ] ifFalse:[
                label := aBuilder labelFor:(label asSymbol)
            ].
            ^ label ? description class defaultIcon
        ].
        description translateLabel == true ifTrue:[
            (appl := aBuilder application) notNil ifTrue:[
                ^ (appl resources string:label) ? label
            ]
        ]
    ].
    ^ label
! !

!DataSetColumn methodsFor:'private'!

drawableAt:aRowNr
    "get the drawable label at an index
    "
    ^ drawableAction value:(dataSet at:aRowNr)
! !

!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

!

containsText
    "returns true if text might exist
    "
    ^ (rendererType ~~ #rowSelector and:[rendererType ~~ #CheckToggle])
!

hasChoices:aRowNr
    ^ (description choicesFor:(dataSet at:aRowNr)) notNil
!

heightOfHighestRow
    "returns the height of the highest row in pixels
    "
    |hObj hMin end|

    hMin := dataSet font heightOn:dataSet device.

    form notNil ifTrue:[
        hMin := hMin max:(buttonExtent y)
    ].

    (hObj := description height) == 0 ifTrue:[
        self containsText ifTrue:[
            "/ search first none empty drawable object
            end := 10 min:dataSet size.

            1 to:end do:[:aRowNr| |lbl|
                lbl := self drawableAt:aRowNr.

                lbl notNil ifTrue:[
                    (lbl respondsTo:#heightOn:) ifTrue:[
                        hObj := lbl heightOn:dataSet
                    ] ifFalse:[
                        hObj := lbl displayString heightOn:dataSet
                    ].
                    ^ hMin max:hObj
                ]
            ]
        ]
    ].
    ^ hMin max:hObj.
! !

!DataSetColumn methodsFor:'searching'!

findRowNrStartingWithChar:aChar start:start stop:stop
    "find the first row starting at start to stop, which drawable label
     starts with the character, aChar. The index of the detected row is
     returned or if no row is found 0.
    "
    |char|

    self containsText ifTrue:[
        char  := aChar asLowercase.

        start to:stop do:[:aRowNr| |lbl|
            lbl := self drawableAt:aRowNr.

            lbl isString ifTrue:[
                (lbl size ~~ 0 and:[(lbl at:1) asLowercase == char]) ifTrue:[
                    ^ aRowNr
                ]
            ] ifFalse:[
                lbl isNil ifFalse:[
                    ^ 0
                ]
            ]
        ]
    ].
    ^ 0

! !

!DataSetColumn class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/DataSetColumn.st,v 1.21 1998-05-20 07:38:03 ca Exp $'
! !