DSVLabelView.st
author penk
Wed, 21 Aug 2002 18:25:59 +0200
changeset 2146 4ae1ec9f5307
parent 2027 e61da28e7ffc
child 2150 5184a8b92c2a
permissions -rw-r--r--
level fixes; labelView draws last partial 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.
"





"{ Package: 'stx:libwidg2' }"

SimpleView subclass:#DSVLabelView
	instanceVariableNames:'dataSet lineDrag columns selection enabled preferredHeight
		handleCursor tabSpacing opaqueColumnResize verticalLabelSpacing'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-DataSet'
!

Object subclass:#LineDrag
	instanceVariableNames:'rootView topX topY botY column minX startX transX'
	classVariableNames:''
	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:]

        dataSet         <DSVColumnView>         column view which shows the columns

        selection       <Integer or nil>        current selected index or nil.

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

        preferredHeight <Integer>               the preferred height of the labelView


    [author:]
        Claus Atzkern

    [see also:]
        DSVColumnView
        DataSetColumnSpec
        DataSetColumn
        DataSetView
"
! !

!DSVLabelView class methodsFor:'accessing'!

tabSpacing
    "returns the tab spacing
    "
    ^ 2
! !

!DSVLabelView class methodsFor:'defaults'!

defaultFont
    ^ DSVColumnView defaultFont
! !

!DSVLabelView methodsFor:'accessing'!

columns:aListOfColumns
    "the list of columns changed
    "
"/    |layout|

    columns         := aListOfColumns.
    preferredHeight := nil.
    selection       := nil.

    self changed:#columnLayout.
"/    dataSet recomputeLayout
"/    isVisible ifTrue:[
"/        dataSet layout:layout.
"/    ].
!

opaqueColumnResize
    ^ opaqueColumnResize
!

opaqueColumnResize:aBoolean
    opaqueColumnResize := aBoolean
! !

!DSVLabelView methodsFor:'drawing'!

invalidate
    (shown) ifTrue:[
        super invalidate
    ]
!

invalidateItemAt:anIndex
    "invalidate rectangle assigned to an item at an index
    "
    |cL xL xR hg|

    (shown) ifTrue:[
        cL := columns at:anIndex ifAbsent:[^ nil].
        xL := self xVisibleOfColNr:anIndex.
        xR := xL + cL width.

        (xL < width and:[xR > 0]) ifTrue:[
            xL := xL max:0.
            xR := xR min:width.
            hg := height - margin - margin.

            self invalidate:(Rectangle left:xL top:margin width:(xR - xL) height:hg)
        ]
    ]
!

redrawColumnsInX:x y:y width:w height:h
    "redraw a rectangle
    "
    |savClip bg fg fgColor bgColor
     inset  "{ Class:SmallInteger }"
     maxX   "{ Class:SmallInteger }"
     lblH  "{ Class:SmallInteger }"
     wt     "{ Class:SmallInteger }"
     x1     "{ Class:SmallInteger }"
     x0     "{ Class:SmallInteger }"
    |
    (shown) ifFalse:[^ self].

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

    columns isEmpty ifTrue:[^ self].

    fgColor := dataSet foregroundColor.
    inset   := dataSet horizontalSpacing + 1.
    maxX    := (x + w) min:(width - margin).
    lblH    := height - margin - margin.
    savClip := clipRect.

    x1 := self xVisibleOfColNr:1.

    columns keysAndValuesDo:[:aKey :aCol| |anItem|
        anItem := aCol label.
        wt := aCol width.
        x0 := x1.
        x1 := x1 + wt.

        (x1 > x and:[x0 < maxX]) ifTrue:[
            |left right rect|

            left  := x0 max:x.
            right := x1 min:maxX.
            rect  := Rectangle left:left top:y width:(right - left) height:h.

            clipRect := nil.
            self clippingRectangle:rect.

            fg := (anItem foregroundColor) ? fgColor.

            (bg := anItem backgroundColor) notNil ifTrue:[
                bg ~= bgColor ifTrue:[
                    self paint:bg.
                    self fillRectangleX:x0 y:margin width:wt height:lblH.
                ]
            ] ifFalse:[
                bg := bgColor
            ].

            self   paint:fg on:bg.            
            anItem redrawX:x0 w:wt h:height inset:inset on:self.
        ]
    ].
!

redrawEdgesX:x y:yTop width:aWidth height:aHeight
    "redraw the edges in the range
    "
    |tabXL desc drawWidth
     maxX "{ Class:SmallInteger }"
     h    "{ Class:SmallInteger }"
     x1   "{ Class:SmallInteger }"
     x0   "{ Class:SmallInteger }"
     y0   "{ Class:SmallInteger }"
     absLabelLevel
    |

    maxX := (x + aWidth) min:(width - margin).
    absLabelLevel := 1.
    x1   := self xVisibleOfColNr:1.

    y0 := margin.
    h  := height - margin - margin.
"/    margin >= absLabelLevel ifTrue:[
"/        y0 := y0 - absLabelLevel.
"/        h := h + absLabelLevel+absLabelLevel.
"/    ].
    columns keysAndValuesDo:[:aKey :aCol|
        desc := aCol description.
        x0   := x1.
        x1   := x1 + aCol width.

        aKey == selection ifTrue:[
            (x1 > x and:[x0 < maxX]) ifTrue:[
                dataSet drawEdgesAtX:x0 y:y0 width:(x1 - x0) height:h level:(absLabelLevel negated) on:self.
            ].
            tabXL notNil ifTrue:[drawWidth := x0 - tabXL].
        ] ifFalse:[
            desc labelHasButtonLayout ifFalse:[
                tabXL notNil ifTrue:[drawWidth := x0 - tabXL].
            ] ifTrue:[
                tabXL isNil ifTrue:[tabXL := x0].
                desc labelIsPartOfGroup ifFalse:[drawWidth := x1 - tabXL].
            ]
        ].
        drawWidth notNil ifTrue:[
            ((tabXL + drawWidth) > x and:[tabXL < maxX]) ifTrue:[
                dataSet drawEdgesAtX:tabXL y:y0 width:drawWidth height:h level:absLabelLevel on:self.
            ].
            drawWidth := tabXL := nil.
        ]
    ].
    tabXL notNil ifTrue:[
        dataSet drawEdgesAtX:tabXL y:y0 width:(x1 - tabXL) height:h level:absLabelLevel on:self
    ].

    x1 < (maxX - absLabelLevel - absLabelLevel - 3) ifTrue:[
        dataSet drawEdgesAtX:x1 y:y0 width:(width-margin-x1-absLabelLevel) height:h level:absLabelLevel on:self
    ].
!

redrawX:x y:y width:wArg height:h
    |savClip w|

    (shown) ifFalse:[^ self].

    w := wArg.
    self redrawColumnsInX:x y:y width:w height:h.

    super redrawX:x y:y width:w height:h.

"/    (x + w) >= (width-margin) ifTrue:[
"/        w := (width-margin) - 1 - x.
"/    ].
    self clippingRectangle:(Rectangle left:x top:margin width:w height:height-margin-margin).
    self redrawEdgesX:x y:y width:w height:h.
    self clippingRectangle:savClip.
! !

!DSVLabelView methodsFor:'event handling'!

buttonMotion:state x:x y:y
    "mouse-button was moved;
     redraw thumb at its new position and, if scroll-mode is asynchronous, 
     the scroll action is performed
    "
    |idx x1 col|

    state = 0 ifTrue:[
        lineDrag := nil.
    ].

    lineDrag notNil ifTrue:[
        (opaqueColumnResize ? (UserPreferences current opaqueTableColumnResizing == true)) ifTrue:[
            lineDrag moveToX:x.      
            dataSet changeWidthOfColumn:lineDrag column deltaX:lineDrag deltaX.
            lineDrag resetDeltaX.    
        ] ifFalse:[
            lineDrag invertLine. "/ off
            lineDrag moveToX:x.      
            lineDrag invertLine. "/ on
        ].
        ^ self.
    ].

    "/ in the resize area ?
    idx := self xVisibleToColNr:(x-tabSpacing).
    col := columns at:idx ifAbsent:nil.

    (col notNil and:[col isResizeable]) ifTrue:[
        x1 := self xVisibleOfColNr:(idx + 1).
        (x between:(x1-tabSpacing) and:(x1+tabSpacing))
        "/ x + tabSpacing > x1 
        ifTrue:[
            ^ self cursor:handleCursor
        ].
    ].

    self cursor:(Cursor normal)
!

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.
    "
    |x1 idx col|

    (enabled and:[shown]) ifFalse:[
        ^ self
    ].

    "/ in the resize area ?
    idx := self xVisibleToColNr:(x-tabSpacing).

    idx ~~ 0 ifTrue:[
        col := columns at:idx ifAbsent:nil.

        col isResizeable ifTrue:[
            x1 := self xVisibleOfColNr:(idx + 1).
            (x between:(x1-tabSpacing) and:(x1+tabSpacing))
            ifTrue:[
                col := columns at:idx ifAbsent:nil.
                self cursor:handleCursor.

                lineDrag := LineDrag new.
                lineDrag column:col
                              x:x
                              y:margin
                              h:(self height + dataSet height)
                           minX:(x1 - col width + col minimumRequiredWidth)
                             on:self.
                (opaqueColumnResize ? (UserPreferences current opaqueTableColumnResizing == true)) ifFalse:[
                    lineDrag invertLine.
                ].
              ^ self
            ]
        ]
    ].

    idx := self xVisibleToColNr:x.
    col := columns at:idx ifAbsent:nil.

    col notNil ifTrue:[
        col label isSelectable ifTrue:[
            self invalidateItemAt:(selection := idx)
        ]
    ].
    self cursor:(Cursor normal).
!

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.
    "
    |selected index column deltaX|

    self cursor:(Cursor normal).

    selection isNil ifTrue:[
        lineDrag notNil ifTrue:[
            (opaqueColumnResize ? (UserPreferences current opaqueTableColumnResizing == true)) ifFalse:[
                 lineDrag invertLine.
            ].
            (opaqueColumnResize ? (UserPreferences current opaqueTableColumnResizing == true)) ifFalse:[
                column   := lineDrag column.
                deltaX   := lineDrag deltaX.

                deltaX abs > 0 "2" ifTrue:[
                    dataSet changeWidthOfColumn:column deltaX:deltaX
                ]
            ].
            lineDrag := nil.
        ].
        ^ self
    ].
    index     := self xVisibleToSelectionIndex:x.
    selected  := index == selection.
    index     := selection.
    selection := nil.

    self invalidateItemAt:index.

    selected ifTrue:[
        (columns at:index) label sendClickMsgTo:(self application)
    ]
!

pointerLeave:state
    "mouse left view - restore cursor.
    "
    self sensor anyButtonPressed ifFalse:[
        self cursor:(Cursor normal)
    ].



!

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

    x1 := self xVisibleOfColNr:1.

    columns keysAndValuesDo:[:index :aCol|
        x0 := x1.
        x1 := x0 + aCol width.

        (x1 > x and:[x0 < x]) ifTrue:[
            ^ index
        ]
    ].
    ^ 0
! !

!DSVLabelView methodsFor:'initialization'!

initStyle
    super initStyle.

    handleCursor := (VariablePanel cursorForOrientation:#horizontal onDevice:device) onDevice:device.
    font := (self class defaultFont).
    "/ self level:0.
    self level:(StyleSheet at:#'dataSet.labelView.level' default:-1).
    verticalLabelSpacing := (StyleSheet at:#'dataSet.labelView.verticalSpace' default:2).
!

initialize
    super initialize.
    "/ super level:(self defaultLevel).

    enabled    := true.
    columns    := #().
    tabSpacing := self class tabSpacing.

    self enableMotionEvents.
! !

!DSVLabelView methodsFor:'instance creation'!

for:aColumnView
    "initialization
    "
    dataSet   := aColumnView.
"/    self level:(dataSet level).
"/    self borderWidth:(dataSet borderWidth).
!

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

!DSVLabelView methodsFor:'queries'!

enabled
    "true, if widget is enabled
    "
    ^ enabled
!

enabled:aState
    "true, if widget is enabled
    "
    enabled := aState.
!

isVisible:aBool

    aBool ~~ self isVisible ifTrue:[
"/        dataSet layout:nil.
        super isVisible:aBool.
        dataSet recomputeLayout.
    ].
!

preferredHeight
    |h|

    preferredHeight notNil ifTrue:[
        ^ preferredHeight
    ].

    h := 0.
    columns do:[:c | h := (c label preferredHeight) max:h ].
    ^ self margin + verticalLabelSpacing + h + verticalLabelSpacing + self margin
!

xVisibleOfColNr:colNr
    "/ must adjust, because dataset includes its own margin, which might be different from ours

    ^ (dataSet xVisibleOfColNr:colNr) - dataSet margin + margin
!

xVisibleToSelectionIndex:x
    "returns the column number assigned to a physical x or nil. If
     the column exists but is not selectable nil is returned.
    "
    |index column|

    (shown and:[enabled]) ifTrue:[
        (     (index  := dataSet xVisibleToColNr:x)  notNil
         and:[(column := columns at:index ifAbsent:nil) notNil
         and:[column label isSelectable]]
        ) ifTrue:[
            ^ index
        ]
    ].
    ^ nil
! !

!DSVLabelView methodsFor:'scrolling'!

copyFromX:x0 y:y0 toX:x1 y:y1 width:w invalidateX:leftX

    (shown) ifFalse:[^ self].

    (self sensor hasDamageFor:self) ifTrue:[
        self invalidate
    ] ifFalse:[
        self   copyFrom:self x:x0 y:y0 toX:x1 y:y1 width:w height:height async:false.
        self invalidate:(Rectangle left:leftX top:0 width:(width - w) height:height)
              repairNow:true
    ]
! !

!DSVLabelView::LineDrag methodsFor:'accessing'!

column
    "return the value of the instance variable 'column' (automatically generated)"

    ^ column
!

deltaX
    "returns the distance x between the start and end action
    "
    ^ topX - startX
!

resetDeltaX
    startX := topX
! !

!DSVLabelView::LineDrag methodsFor:'dragging'!

invertLine
    "invert for a line
    "
    |c rootDevice|

    rootDevice := rootView device.

    rootView clippedByChildren:false.

    rootView xoring:[
        rootView paint:(Color colorId:(rootDevice blackpixel bitXor:rootDevice whitepixel)).
        rootView lineWidth:2.
        rootView displayLineFromX:topX y:topY toX:topX y:botY.
        rootView flush
    ]

    "Modified: / 10.10.2001 / 15:14:25 / cg"
!

moveToX:viewX
    topX := (minX max:viewX) + transX.
! !

!DSVLabelView::LineDrag methodsFor:'setup'!

column:aColumn x:x y:y h:h minX:aMinX on:aView
    |device point|

    column   := aColumn.
    device   := aView device.
    rootView := device rootView.
    point    := device translatePoint:(x@y) fromView:aView toView:rootView.
    topX     := point x.
    topY     := point y.
    botY     := topY + h.
    minX     := aMinX.
    startX   := topX.
    transX   := topX - x.
! !

!DSVLabelView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/DSVLabelView.st,v 1.42 2002-08-21 16:25:51 penk Exp $'
! !