DataSetColumn.st
author Claus Gittinger <cg@exept.de>
Fri, 25 Sep 1998 17:01:16 +0200
changeset 1147 2d0b9fc2422c
parent 1133 619b0afc557a
child 1186 8da80b8ed338
permissions -rw-r--r--
new feature: allow collections of strings, icons ... for a cell

"
 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 minWidth width description buttonExtent
		drawableAction shownValue rendererType backgroundColor
		rowSeparatorSelector showColSeparator showRowSeparator
		foregroundColor fgSelector bgSelector columnAlignment label
		readSelector numArgsToReadSelector columnAdaptor'
	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)

        dataSet         <DSVColumnView>         the view it belongs to

        minWidth        <Integer>               minimum required width by the column

        width           <Integer>               width of column

        description     <DataSetColumnSpec>     the column description

        buttonExtent    <Point>                 extent of drawable form

        drawableAction  <Action>                action to access the printable
                                                label of a cell

        rendererType    <Type>                  renderer type (cached value from
                                                the 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

        columnAlignment <Symbol>                align text/icon #left #right or #center
                                                in row (on default: #left).

        label           <label/icon or nil>     label resolved by the builder shown
                                                in the column description field.

        readSelector    <Symbol>                cached readSelector (from the spec)

        numArgsToReadSelector <Integer>         number of arguments to the readSelector

        columnAdaptor   <nil or any>            if non-nil, that one is asked (via
                                                read-writeSelectors to extract a column
                                                from a row object.
                                                If nil, the row object is used itself.

        showColSeparator <Boolean>              true: vertical separators are enabled;
                                                separator between columns

        showRowSeparator <Boolean>              true: horizontal separators are enabled;
                                                separator between rows

        rowSeparatorSelector <Selector or nil>  access specific showRowSeparator state
                                                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
    "
    ^ self extractColFromRow:(dataSet at:aRowNr).
!

at:aRowNr put:something
    "set the value of the raw at an index, aRowNr
    "
    |row newRow|

    row := dataSet at:aRowNr.
    newRow := self storeCol:something inRow:row.
    newRow ~~ row ifTrue:[
        dataSet dataSetView listAt:aRowNr put:newRow.
    ]

    "Modified: / 7.8.1998 / 22:17:27 / cg"
!

backgroundColor
    "returns the background color or nil
    "
    ^ backgroundColor == dataSet backgroundColor ifTrue:[nil]
                                                ifFalse:[backgroundColor]

!

backgroundColorFor:aRowNr
    |bg|

    bgSelector notNil ifTrue:[
        (bg := (dataSet at:aRowNr) perform:bgSelector) notNil ifTrue:[
            ^ bg
        ]
    ].
    ^ backgroundColor

!

description
    "returns the column description
    "
    ^ description


!

foregroundColor
    "returns the foreground color or nil
    "
    ^ foregroundColor == dataSet foregroundColor ifTrue:[nil]
                                                ifFalse:[foregroundColor]

!

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


!

rendererType
    "returns my renderer type
    "
    ^ rendererType
!

width
    "returns the width in pixels
    "
    |max w|

    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

            max := 10 min:dataSet size.

            1 to:max do:[:i|
                w := self widthOfLabel:(shownValue value:(dataSet at:i)).
                width := width max:w
            ].
            description editorType ~~ #None ifTrue:[
                width := width + (dataSet font widthOn:dataSet device)
            ].
        ].
        width := width + buttonExtent x.
        width := width max:(4 + (label preferredExtent 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'!

drawLabel:aLabel atX:xLeft y:yTop
    "redraw label
    "
    |x space|

    space := dataSet horizontalSpacing.

    columnAlignment == #left ifTrue:[
        x  := xLeft + space.
    ] ifFalse:[
        x := width - (aLabel widthOn:dataSet).

        columnAlignment == #right ifTrue:[x := x - space]
                                 ifFalse:[x := x // 2].
        x := (xLeft + x) max:0.
    ].
    aLabel isImageOrForm ifTrue:[
        aLabel displayOn:dataSet x:x y:yTop.
      ^ self
    ].

    aLabel displayOn:dataSet x:x y:(yTop + dataSet rowFontAscent)
!

drawLabelsAtX:xLeft y:yTop h:h from:start to:stop
    "redraw labels from start to stop
    "
    |fg bg label row isSel
     y       "{ Class:SmallInteger }"
     yT      "{ Class:SmallInteger }"
     x       "{ Class:SmallInteger }"
     hspace  "{ Class:SmallInteger }"
     ascent  "{ Class:SmallInteger }"
     lblHg   "{ Class:SmallInteger }"
    |
    yT := yTop.
    ascent := dataSet rowFontAscent.
    hspace := dataSet horizontalSpacing.

    start to:stop do:[:anIndex|
        row := dataSet at:anIndex.
        y := yT.
        x := xLeft.

     "/ GET BACKGROUND AND FOREGROUND-COLOR
     "/ ===================================

        isSel := dataSet isSelected:anIndex inColumn:columnNumber.

        isSel ifTrue:[
            (      description editorType ~~ #None
              and:[dataSet selectedColIndex == columnNumber]
            ) ifTrue:[
                isSel := false
            ]
        ].

        (isSel and:[description showSelectionHighLighted]) ifTrue:[
            "/ SHOW SELECTED( MUST REDRAW BACKGROUND )
            "/ =======================================
            fg := dataSet hgLgFgColor.
            bg := dataSet hgLgBgColor.
            dataSet paint:bg.
            dataSet fillRectangleX:x y:y width:width height:h.
        ] ifFalse:[
            bgSelector notNil ifTrue:[
                "/ MUST REDRAW BACKGROUND
                "/ ======================
                (bg := row perform:bgSelector) notNil ifTrue:[
                    bg := dataSet colorOnDevice:bg
                ] ifFalse:[
                    bg := backgroundColor
                ].
                dataSet paint:bg.
                dataSet fillRectangleX:x y:y width:width height:h.
            ] ifFalse:[
                bg := backgroundColor
            ].

            (fgSelector notNil and:[(fg := row perform:fgSelector) notNil]) ifTrue:[
                fg := dataSet colorOnDevice:fg
            ] ifFalse:[
                fg := foregroundColor
            ]
        ].

     "/ GET AND DRAW LABEL
     "/ ==================
        rendererType == #rowSelector ifTrue:[
            isSel ifTrue:[
                label := dataSet rowSelectorForm.
                x  := x + hspace.
            ] ifFalse:[
                label := nil
            ]
        ] ifFalse:[
            (isSel and:[dataSet hasOpenEditor]) ifTrue:[
                label := nil
            ]  ifFalse:[
                label := shownValue value:row
            ]
        ].
        label notNil ifTrue:[
            lblHg := self heightOfLabel:label.

            lblHg ~~ 0 ifTrue:[
                y := y + (h - lblHg // 2).
                dataSet paint:fg on:bg.

                (label isSequenceable and:[label isString not]) ifFalse:[
                    self drawLabel:label atX:x y:y
                ] ifTrue:[
                    label do:[:el|
                        el notNil ifTrue:[
                            self drawLabel:el atX:x y:y.
                            y := y + (el heightOn:dataSet).
                        ]
                    ]
                ].
            ]
        ].
        yT := yT + h
    ]


!

drawSeparatorsAtX:xLeft y:yTop h:h from:start to:stop
    "redraw separators for cells between start and stop
    "
    |is3D
     xL    "{ Class:SmallInteger }"
     xR    "{ Class:SmallInteger }"
     yB    "{ Class:SmallInteger }"
     yT    "{ Class:SmallInteger }"
     times "{ Class:SmallInteger }"
    |
    (showColSeparator or:[showRowSeparator]) ifFalse:[
        ^ self
    ].
    is3D := dataSet has3Dseparators.

    is3D ifTrue:[dataSet paint:(dataSet separatorDarkColor)]
        ifFalse:[dataSet paint:(dataSet foregroundColor)].

    times := stop - start + 1.
    xL    := xLeft.
    xR    := xL - 1 + width.

    showRowSeparator ifTrue:[
     "/ DRAW SEPARATORS AT BOTTOM( DARK COLOR )
     "/ =======================================
        yB := yTop - 1 + h.

        rowSeparatorSelector isNil ifTrue:[
            times timesRepeat:[
                dataSet displayLineFromX:xL y:yB toX:xR y:yB.
                yB := yB + h.
            ]
        ] ifFalse:[
            start to:stop do:[:idx|
                ((dataSet at:idx) perform:rowSeparatorSelector) ~~ false ifTrue:[
                    dataSet displayLineFromX:xL y:yB toX:xR y:yB
                ].
                yB := yB + h.
            ]
        ]
    ].

    showColSeparator ifTrue:[
     "/ DRAW SEPARATORS AT RIGHT( DARK COLOR )
     "/ ======================================
        yT := yTop.

        times timesRepeat:[
            dataSet displayLineFromX:xR y:yT toX:xR y:(yT - 1 + h).
            yT := yT + h.
        ]
    ].

    is3D ifFalse:[
        ^ self
    ].

    dataSet paint:(dataSet separatorLightColor).

    (     columnNumber == 1
      or:[(dataSet columnAt:(columnNumber - 1)) showColSeparator]
    ) ifTrue:[

     "/ DRAW SEPARATORS AT LEFT( LIGHT COLOR )
     "/ ======================================
        yT := yTop.

        times timesRepeat:[
            dataSet displayLineFromX:xL y:yT toX:xL y:(yT - 1 + h).
            yT := yT + h.
        ].
    ] ifFalse:[
        xL := xL - 1
    ].

    showRowSeparator ifTrue:[
     "/ DRAW SEPARATORS AT TOP( LIGHT COLOR )
     "/ =====================================
        yT := yTop.

        rowSeparatorSelector isNil ifTrue:[
            times timesRepeat:[
                dataSet displayLineFromX:xL y:yT toX:xR y:yT.
                yT := yT + h.
            ]
        ] ifFalse:[
         "/ CHECK WHETHER PREVIOUS ROW HAS A SEPARATOR AT BOTTOM
         "/ ====================================================
            start to:stop do:[:idx|
                (    idx == 1
                  or:[((dataSet at:(idx - 1)) perform:rowSeparatorSelector) ~~ false]
                ) ifTrue:[
                    dataSet displayLineFromX:xL y:yT toX:xR y:yT.
                ].
                yT := yT + h.
            ]
        ]
    ].


!

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

!

redrawX:xLeft y:yTop h:h from:start to:stop
    "redraw rows between start and stop
    "
    |rH "{ Class:SmallInteger }"
     y  "{ Class:SmallInteger }"
    |
    rH := dataSet rowHeight.

    bgSelector isNil ifTrue:[
        dataSet paint:backgroundColor.
        dataSet fillRectangleX:xLeft y:yTop width:width height:h
    ].

 "/ DRAW CELLS: BACKGROUND/FOREGROUND/LABEL
 "/ =======================================
    self drawLabelsAtX:xLeft y:yTop h:rH from:start to:stop.

 "/ DRAW INDICATORS
 "/ ===============
    (rendererType == #ComboBox or:[rendererType == #ComboList]) ifTrue:[
        y := yTop.
        start to:stop do:[:i|
            (self hasChoices:i) ifTrue:[
                dataSet drawComboButtonAtX:xLeft y:y w:width
            ].
            y := y + rH.
        ]
    ] ifFalse:[
        rendererType == #CheckToggle ifTrue:[
            y := yTop.
            start to:stop do:[:i|
                dataSet drawCheckToggleAtX:xLeft y:y w:width
                                    state:(self extractColFromRow:(dataSet at:i)).
                y := y + rH.
            ]
        ]
    ].

 "/ DRAW SEPARATORS
 "/ ===============
    self drawSeparatorsAtX:xLeft y:yTop h:rH from:start to:stop
! !

!DataSetColumn methodsFor:'editing'!

editorAt:aRowNr
    |val row index|

    row := (dataSet at:aRowNr).
    val := self extractColFromRow:row.

    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

! !

!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 label:aLabel
    "instance creation; set attributes dependent on the description
    "
    |device selector format idx type oldFont newFont args|

    columnNumber     := aNumber.
    dataSet          := aDSVColumnView.
    label            := aLabel.
    description      := aDescription.
    rendererType     := description rendererType.
    width            := nil.
    device           := dataSet device.
    shownValue       := [:aRow| nil ].
    rowSeparatorSelector := description rowSeparatorSelector.
    fgSelector       := description foregroundSelector.
    bgSelector       := description backgroundSelector.
    showColSeparator := description showColSeparator.
    showRowSeparator := description showRowSeparator.
    columnAdaptor    := dataSet columnAdaptor.
    buttonExtent     := 0 @ 0.
    columnAlignment  := #left.

    (readSelector := description readSelector) notNil ifTrue:[
        numArgsToReadSelector := readSelector numArgs.
    ] ifFalse:[
        numArgsToReadSelector := 0
    ].

    (backgroundColor := description backgroundColor) isNil ifTrue:[
        backgroundColor := dataSet backgroundColor
    ] ifFalse:[
        backgroundColor := backgroundColor on:dataSet device
    ].

    (foregroundColor := description foregroundColor) isNil ifTrue:[
        foregroundColor := dataSet foregroundColor
    ] ifFalse:[
        foregroundColor := foregroundColor on:dataSet device
    ].

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

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

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

    selector := description printSelector.

    selector notNil ifTrue:[
        args := selector numArgs.
        args == 0 ifTrue:[
            shownValue := [:aRow| aRow perform:selector ]
        ] ifFalse:[
            args == 1 ifTrue:[
                shownValue := [:aRow| aRow perform:selector with:dataSet ]
            ] ifFalse:[
                shownValue := [:aRow| aRow perform:selector with:dataSet with:columnNumber ]
            ]
        ].
        ^ 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'.

        shownValue := [:aRow||n|
            n := self extractColFromRow:aRow.
            n isReal ifTrue:[n := n asFloat printfPrintString:format].
            n
        ]
    ] ifFalse:[         "/ default: no format string
        shownValue := [:aRow| self extractColFromRow:aRow ]
    ]


! !

!DataSetColumn methodsFor:'private'!

extractColFromRow:aRow

    columnAdaptor notNil ifTrue:[
        numArgsToReadSelector == 1 ifTrue:[
            ^ columnAdaptor perform:readSelector with:aRow
        ].
        ^ columnAdaptor perform:readSelector with:aRow with:columnNumber
    ].

    numArgsToReadSelector == 0 ifTrue:[
        ^ aRow perform:readSelector
    ].
    ^ aRow perform:readSelector with:columnNumber
!

storeCol:newValue inRow:aRow
    |writeSelector numArgs|

    writeSelector := description writeSelector.
    numArgs := writeSelector numArgs.

    columnAdaptor notNil ifTrue:[
        numArgs == 2 ifTrue:[
            ^ columnAdaptor perform:writeSelector with:aRow with:newValue
        ].
        ^ columnAdaptor perform:writeSelector with:aRow with:columnNumber with:newValue
    ].

    numArgs == 1 ifTrue:[
        aRow perform:writeSelector with:newValue
    ] ifFalse:[
        aRow perform:writeSelector with:columnNumber with:newValue
    ].
    ^ aRow

! !

!DataSetColumn methodsFor:'queries'!

canSelect:aRowNr
    "returns true if cell in column is selectable
    "
    |s|

    description canSelect ifTrue:[
        (s := description selectSelector) notNil ifTrue:[
            columnAdaptor notNil ifTrue:[
                s numArgs == 2 ifTrue:[
                    ^ columnAdaptor perform:s with:(dataSet at:aRowNr) with:columnNumber
                ].
                ^ columnAdaptor perform:s with:(dataSet at:aRowNr)
            ].
            s numArgs == 1 ifTrue:[
                ^ (dataSet at:aRowNr) perform:s with:columnNumber
            ].
            ^ (dataSet at:aRowNr) perform:s
        ].
        ^ true
    ].
    ^ false

    "Modified: / 7.8.1998 / 22:49:20 / cg"
!

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) 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  := shownValue value:(dataSet at:aRowNr).
                hObj := self heightOfLabel:(shownValue value:(dataSet at:aRowNr)).
                hMin := hMin max:hObj
            ]
        ]
    ].
    ^ hMin max:hObj.
!

heightOfLabel:aLabel
    "returns the height of the label
    "
    |h l|

    aLabel isNil ifTrue:[ ^ 0 ].

    (aLabel isSequenceable and:[aLabel isString not]) ifFalse:[
        (aLabel respondsTo:#heightOn:) ifTrue:[l := aLabel]
                                      ifFalse:[l := aLabel displayString].
        ^ l heightOn:dataSet
    ].
    h := 0.

    aLabel do:[:el|
        (el respondsTo:#heightOn:) ifTrue:[l := el]
                                  ifFalse:[l := el displayString].
        h := h + (el heightOn:dataSet)
    ].
    ^ h

!

heightOfLabelAt:aRowNr
    "returns the height of the label at a row in pixels
    "
    ^ self heightOfLabel:(shownValue value:(dataSet at:aRowNr)).
!

showColSeparator
    "returns true if column separator is on
    "
    ^ showColSeparator
!

showSelectionHighLighted
    "returns true if selection is highLighted
    "
    ^ description showSelectionHighLighted ~~ false
!

widthOfLabel:aLabel
    "returns the width of the label
    "
    |w l|

    aLabel isNil ifTrue:[ ^ 0 ].

    (aLabel isSequenceable and:[aLabel isString not]) ifFalse:[
        (aLabel respondsTo:#widthOn:) ifTrue:[l := aLabel]
                                     ifFalse:[l := aLabel displayString].
        ^ l widthOn:dataSet
    ].
    w := 0.

    aLabel do:[:el|
        (el respondsTo:#widthOn:) ifTrue:[l := el]
                                 ifFalse:[l := el displayString].
        w := w max:(el widthOn:dataSet)
    ].
    ^ w
! !

!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 := shownValue value:(dataSet at:aRowNr).

            (lbl isSequenceable and:[lbl isString not]) ifTrue:[
                lbl := lbl at:1 ifAbsent:nil
            ].

            (lbl respondsTo:#string) ifTrue:[
                lbl := lbl string.
                (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.37 1998-09-25 15:01:16 cg Exp $'
! !