DSVLabelView.st
author Claus Gittinger <cg@exept.de>
Fri, 11 Jun 1999 19:22:15 +0200
changeset 1408 1cda0a4fb566
parent 1269 f33ad4d38b5b
child 1426 9a067c26db45
permissions -rw-r--r--
use invalidate... insteat of redraw...

"
 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 enteredItem'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-DataSet'
!

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

        enabled         <Boolean>               if a press action exists on a column
                                                entry, this action could be enabled or
                                                disabled.

        enteredItem     <Item>                  current entered item; if a press action
                                                is defined, this itenm is highlighted.
                                                Used to redraw the item not highlighted
                                                if the item is leaved.


    [author:]
        Claus Atzkern

    [see also:]
        DSVColumnView
        DataSetColumnSpec
        DataSetColumn
        DataSetView
"



! !

!DSVLabelView class methodsFor:'constants'!

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

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

invalidateItem:anItem
    "invalidate rectangle assigned to an item
    "
    shown ifTrue:[
        self invalidate:(anItem layout)
    ]
!

invalidateX:x y:y width:w height:h
    "invalidate a rectangle
    "
    shown ifTrue:[
        self invalidate:(Rectangle left:x top:y width:w height:h)
    ].
!

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).
            anItem == enteredItem ifTrue:[lv := lv + 1].
            columnView drawEdgesAtX:left y:0 width:width height:height level:lv on:self
        ]
    ].
    self clippingRectangle:savClip.



! !

!DSVLabelView methodsFor:'event handling'!

buttonMotion:state x:x y:y
    |sensor|

    (selection isNil and:[(sensor := self sensor) notNil]) ifTrue:[
        self itemEntered:(self detectItemAtX:x y:y)
    ].
    super buttonMotion:state x:x y:y
!

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|

    self itemEntered:nil.

    enabled ifTrue:[
        (     button == 1
         and:[selection isNil
         and:[(item := self detectItemAtX:x y:y) notNil
         and:[item isSelectable]]]
        ) ifTrue:[
            self invalidateItem:(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|

    self itemEntered:nil.

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

        self invalidateItem:item.

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

!

itemEntered:anItemOrNil
    |prevEntered|

    enteredItem == anItemOrNil ifTrue:[
        ^ self
    ].
    prevEntered := enteredItem.
    enteredItem := anItemOrNil.

    prevEntered notNil ifTrue:[
        prevEntered isSelectable ifTrue:[
            self invalidateItem:prevEntered
        ]
    ].

    enteredItem notNil ifTrue:[
        enteredItem isSelectable ifTrue:[
            self invalidateItem:enteredItem
        ]
    ]
!

pointerLeave:state
    self itemEntered:nil.
    super pointerLeave:state
! !

!DSVLabelView methodsFor:'instance creation'!

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

!

initialize
    super initialize.
    self enableMotionEvents.

! !

!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 invalidate.
    ].


!

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

    (pX := aPoint x) == 0 ifTrue:[
        ^ self
    ].
    (self sensor hasExposeEventFor:self) ifTrue:[
        ^ self invalidate
    ].
    point := Point x:(aPoint x) y:0.
    items do:[:anItem| anItem originChanged:point].

    x := pX abs.

    (w := self width - x) < 20 ifTrue:[
        ^ self invalidate
    ].
    h := self height.

    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 waitForExpose.
    self invalidateX:w y:0 width:x height:h.


!

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

    self itemEntered:nil.
    items := OrderedCollection new.

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

        columnView columnsDo:[:aColumn||item|
            items add:(item := aColumn label).
            height := (item preferredExtent y) max:height.
        ].
        height := height + self class verticalInset.
        self updateLayoutsHeight:height.
        self bottomInset:height negated.
    ].
    self invalidate.

! !

!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 + 1.
    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 class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/DSVLabelView.st,v 1.22 1999-06-11 17:22:04 cg Exp $'
! !