DSVLabelView.st
author ca
Wed, 03 Jun 1998 16:30:36 +0200
changeset 907 3250a67fcce2
parent 893 7e52a293a3da
child 1085 cebea5318863
permissions -rw-r--r--
draw for each column the label

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





SimpleView subclass:#DSVLabelView
	instanceVariableNames:'items columnView selection enabled'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-DataSet'
!

Object subclass:#Item
	instanceVariableNames:'label selector argument adjust font fgColor bgColor layout
		preferredExtent'
	classVariableNames:'DefaultLayout'
	poolDictionaries:''
	privateIn:DSVLabelView
!

!DSVLabelView 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
"
    shows the labels assigned to the column descriptions. Used by the
    DataSetView

    [Instance variables:]

        columnView      <DSVColumnView>         column view which shows the columns

        items           <OrderedCollection>     list of items; each item describes
                                                one column.

        selection       <Item or nil>           current selected item or nil. An none
                                                empty selection exists during pressing
                                                a button.


    [author:]
        Claus Atzkern

    [see also:]
        DSVColumnView
        DataSetColumnSpec
        DataSetColumn
        DataSetView
"



! !

!DSVLabelView class methodsFor:'constants'!

activeLevel
    "returns the active level; item is pressed
    "
    ^ -2
!

passiveLevel
    "returns the passive level; item not pressed
    "
    ^ 1
!

verticalInset
    "returns the vertical inset added to the maximum label height
    "
    ^ 8



! !

!DSVLabelView methodsFor:'accessing'!

columnView
    ^ columnView
!

enabled
    ^ enabled
!

enabled:aState
    enabled := aState.
! !

!DSVLabelView methodsFor:'drawing'!

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

!

redrawItem:anItem
    "redraw rectangle assigned to an item
    "
    |layout|

    layout := anItem layout.

    self redrawX:(layout left)
               y:(layout top)
           width:(layout width)
          height:(layout height).

! !

!DSVLabelView methodsFor:'drawing basics'!

redrawX:x y:y width:w height:h
    "redraw a rectangle
    "
    |inset savClip bg fg fgColor bgColor maxX layout left width actLvl pasLvl lv|

    shown ifFalse:[
        ^ self
    ].

    bgColor := columnView backgroundColor.
    fgColor := columnView foregroundColor.
    inset   := columnView horizontalSpacing.
    actLvl  := self class activeLevel.
    pasLvl  := self class passiveLevel.
    maxX    := x + w.

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

    items isEmpty ifTrue:[
        ^ self
    ].
    savClip := clipRect.

    self clippingRectangle:(Rectangle left:x top:y width:w height:h).

    items do:[:anItem|
        layout := anItem layout.
        left   := layout left.
        width  := layout width.

        (left < maxX and:[layout right > x]) ifTrue:[
            (bg := anItem backgroundColor) notNil ifTrue:[
                bg ~= bgColor ifTrue:[
                    self paint:bg.
                    self fillRectangleX:left y:y width:width height:h.
                ]
            ] ifFalse:[
                bg := bgColor
            ].

            fg := (anItem foregroundColor) ? fgColor.
            lv := selection == anItem ifTrue:[actLvl] ifFalse:[pasLvl].
            self paint:fg on:bg.
            anItem redrawLabelOn:self hInset:inset + (lv abs).
            columnView drawEdgesAtX:left y:0 width:width height:height level:lv on:self
        ]
    ].
    self clippingRectangle:savClip.



! !

!DSVLabelView methodsFor:'event handling'!

buttonPress:button x:x y:y
    "handle a button press event; checks whether the item under the mouse
     is selectable. If true, the selection is set to the item.
    "
    |item|

    enabled ifTrue:[
        (     button == 1
         and:[selection isNil
         and:[(item := self detectItemAtX:x y:y) notNil
         and:[item isSelectable]]]
        ) ifTrue:[
            self redrawItem:(selection := item)
        ]
    ].
    super buttonPress:button x:x y:y


!

buttonRelease:button x:x y:y
    "handle a button press event; checks whether the item under the mouse
     is the selected item. If true, the application is informed.
    "
    |item same layout arg appl|

    ( button == 1 and:[selection notNil]) ifTrue:[
        same      := (self detectItemAtX:x y:y) == selection.
        item      := selection.
        layout    := item layout.
        selection := nil.

        self redrawItem:item.

        same ifTrue:[
            item sendClickMsgTo:(self application)
        ]
    ].
    super buttonRelease:button x:x y:y.

! !

!DSVLabelView methodsFor:'instance creation'!

for:aColumnView
    "initialization
    "
    enabled := true.
    items := OrderedCollection new.
    columnView := aColumnView.

! !

!DSVLabelView methodsFor:'notifications'!

columnsLayoutChanged
    "layout of columns changed and thus the layout of
     all items.
    "
    items size == columnView numberOfColumns ifFalse:[
        self columnsSizeChanged
    ] ifTrue:[
        self updateLayoutsHeight:(self height).
        self redraw.
    ].


!

columnsOriginChanged:aPoint
    "the origin of the columnView changed caused by a scroll operation
    "
    |point pX x w h|

    (pX := aPoint x) == 0 ifTrue:[
        ^ self
    ].

    point := Point x:(aPoint x) y:0.
    items do:[:anItem| anItem originChanged:point].

    (self sensor hasExposeEventFor:self) ifTrue:[
        ^ self invalidateRepairNow:true
    ].

    x := pX abs.
    w := self width - x.
    h := self height.

    w < 20 ifTrue:[
        ^ self redraw
    ].

    self catchExpose.

    pX < 0 ifTrue:[
        self copyFrom:self x:0 y:0 toX:x y:0 width:w height:h async:true.
        w := 0.
    ] ifFalse:[
        self copyFrom:self x:x y:0 toX:0 y:0 width:w height:h async:true.
    ].
    self redrawX:w y:0 width:x height:h.
    self waitForExpose.


!

columnsSizeChanged
    "the list of columns changed; recreate all items
    "
    |height font|

    items := OrderedCollection new.

    columnView numberOfColumns ~~ 0 ifTrue:[
        font   := columnView font.
        height := 0.

        columnView columnsDo:[:aColumn||item|
            items add:(item := Item column:aColumn font:font on:self).
            height := (item preferredExtent y) max:height.
        ].
        height := height + self class verticalInset.
        self updateLayoutsHeight:height.
        self bottomInset:height negated.
    ].
    self redraw.

! !

!DSVLabelView methodsFor:'private'!

detectItemAtX:x y:y
    "returns item at point x@y or nil
    "
    items do:[:anItem|
        (anItem layout containsPointX:x y:y) ifTrue:[ ^ anItem ]
    ].
    ^ nil

!

updateLayoutsHeight:h
    "update the rectangle layout for each item based on a height
    "
    |i x w|

    i := 1.
    x := columnView margin - columnView xOriginOfContents.
    columnView has3Dseparators ifFalse:[ x := x + 1].

    columnView columnsDo:[:aCol|
        w := aCol width.
        (items at:i) layout:(Rectangle origin:(x @ 0) extent:(w @ h)).
        i := i + 1.
        x := x + w.
    ].
! !

!DSVLabelView::Item class methodsFor:'constants'!

defaultLayout
    "returns the default layout used for initialization
    "
    DefaultLayout isNil ifTrue:[
        DefaultLayout := Rectangle left:0 right:0 top:0 bottom:0
    ].
    ^ DefaultLayout


! !

!DSVLabelView::Item class methodsFor:'documentation'!

documentation
"
    describes the label of one column entry.

    [Instance variables:]

        label           <Object>        the label of the column

        selector        <Symbol>        a selector, which is evaluated with the argument
                                        if the item is selected and the button is released.

        argument        <Object>        user defined argument for the selector.

        adjust          <Symbol>        align label left, right or center; default is center

        font            <Font>          font used to dispaly the label; if the font is
                                        undefined, the default font is used.

        fgColor         <Color>         foreground color for the label; if the fgColor is
                                        undefined, the default foreground color is used.

        bgColor         <Color>         background color for the label; if the bgColor is
                                        undefined, the default background color is used.

        layout          <Rectangle>     the layout of the item

        preferredExtent <Point>         preferred extent of the label


    [author:]
        Claus Atzkern
"
! !

!DSVLabelView::Item class methodsFor:'instance creation'!

column:aColumn font:aFont on:aGC
    "create a new item for a column
    "
    ^ (self new) column:aColumn font:aFont on:aGC


! !

!DSVLabelView::Item methodsFor:'accessing'!

backgroundColor
    "returns the background color of the column or nil
    "
    ^ bgColor


!

foregroundColor
    "returns the foreground color of the column or nil
    "
    ^ fgColor


!

label
    "returns the label of the column or nil
    "
    ^ label


! !

!DSVLabelView::Item methodsFor:'accessing dimensions'!

layout
    "returns the item's layout, a Rectangle
    "
    ^ layout


!

layout:aLayout
    "set the item's layout, a Rectangle
    "
    layout := aLayout


!

preferredExtent
    "returns the preferred extent of the label
    "
    ^ preferredExtent


! !

!DSVLabelView::Item methodsFor:'actions'!

sendClickMsgTo:aReceiver
    "inform the receiver of a button release notification
    "
    (aReceiver notNil and:[selector notNil]) ifTrue:[
        selector numArgs ~~ 0 ifTrue:[
            aReceiver perform:selector with:argument
        ] ifFalse:[
            aReceiver perform:selector
        ]
    ]

! !

!DSVLabelView::Item methodsFor:'drawing'!

redrawLabelOn:aGC hInset:hInset
    "redraw the label; the background is cleared and the paint is set
    "
    |x y|

    label isNil ifTrue:[
        ^ self
    ].

    adjust == #left ifTrue:[
        x := layout left + hInset.
    ] ifFalse:[
        adjust == #right ifTrue:[
            x := layout right - preferredExtent x - hInset        
        ] ifFalse:[
            x := layout left + (((layout width - preferredExtent x) // 2) max:0)
        ]
    ].
    y := layout top + (layout height - preferredExtent y // 2).

    font notNil ifTrue:[
        aGC font:font.
        y := y + font ascent.
    ].

    label displayOn:aGC x:x y:y.


! !

!DSVLabelView::Item methodsFor:'instance creation'!

column:aColumn font:aFont on:aGC
    "create instance for a column
    "
    |img|

    label    := aColumn label.
    selector := aColumn description labelActionSelector.
    argument := (aColumn description labelActionArgument) ? label.

    adjust := aColumn labelAlignment.
    layout := self class defaultLayout.

    (fgColor := aColumn labelForegroundColor) notNil ifTrue:[
        fgColor := fgColor on:(aGC device)
    ].

    (bgColor := aColumn labelBackgroundColor) notNil ifTrue:[
        bgColor := bgColor on:(aGC device)
    ].

    label notNil ifTrue:[
        label isString ifFalse:[
            label := label on:aGC device.

            label isImage ifTrue:[
                label clearMaskedPixels
            ]
        ] ifTrue:[
            label withoutSeparators isEmpty ifTrue:[
                label := nil
            ]
        ].

        (label respondsTo:#string) ifTrue:[
            font := aColumn labelFont.

            font notNil ifTrue:[ font := font on:(aGC device) ]
                       ifFalse:[ font := aFont ].

            aGC font:font.

            label class == LabelAndIcon ifTrue:[
                label := label on:(aGC device).
                (img := label image) isImage ifTrue:[img clearMaskedPixels].
                (img := label icon)  isImage ifTrue:[img clearMaskedPixels].
            ]
        ]
    ].

    preferredExtent := label notNil ifTrue:[ Point x:(label widthOn:aGC) y:(label heightOn:aGC) ]
                                   ifFalse:[ 0 @ 0 ].

! !

!DSVLabelView::Item methodsFor:'notification'!

originChanged:aDeltaPoint
    "called when the origin of the layout changed; scrolling left or right
    "
    |origin extent|

    origin := layout origin.
    extent := layout extent.

    layout origin:(origin - aDeltaPoint) extent:extent


! !

!DSVLabelView::Item methodsFor:'queries'!

isSelectable
    "returns true if the item is selectable; a valid selector
     to notify the receiver for a release button event exists
    "
    ^ selector notNil


! !

!DSVLabelView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/DSVLabelView.st,v 1.16 1998-06-03 14:30:36 ca Exp $'
! !