VariableVerticalPanel.st
author claus
Thu, 13 Jan 1994 01:18:51 +0100
changeset 24 966098a893f8
parent 23 69f1ba57f67a
child 38 4b9b70b2cc87
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1991 by Claus Gittinger
              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.
"

View subclass:#VariableVerticalPanel
         instanceVariableNames:'movedHandle prev start
                                barHeight barWidth separatingLine
                                shadowForm lightForm
                                handlePosition 
                                handleColor noColor'
         classVariableNames:''
         poolDictionaries:''
         category:'Views-Layout'
!

VariableVerticalPanel comment:'

COPYRIGHT (c) 1991 by Claus Gittinger
              All Rights Reserved

a View to separate its subviews vertically by a movable bar;
the size-ratios of the subviews can be changed by moving this bar.

The bar-handle is either an exposed knob (style == #motif)
or the forms defined in Scroller (style ~~ #motif)

$Header: /cvs/stx/stx/libwidg/VariableVerticalPanel.st,v 1.6 1994-01-13 00:18:51 claus Exp $

written summer 91 by claus
'!

!VariableVerticalPanel class methodsFor:'defaults'!

shadowFormOn:aDisplay
    "use same handle as Scroller"

    ^ Scroller handleShadowFormOn:aDisplay
!

lightFormOn:aDisplay
    "use same handle as Scroller"

    ^ Scroller handleLightFormOn:aDisplay
! !

!VariableVerticalPanel methodsFor:'initializing'!

initialize
    super initialize.
    noColor := Color noColor.
    handleColor := Black.
!

initStyle
    |defaultPosition|

    super initStyle.

    (style == #next) ifTrue:[
        shadowForm := self class shadowFormOn:device.
        lightForm := self class lightFormOn:device.
        defaultPosition := #center.

        self barHeight:(shadowForm height + 2).
        barWidth := shadowForm width
    ] ifFalse:[
        defaultPosition := #right
    ].
    handlePosition := resources at:'HANDLE_POSITION' default:defaultPosition.
    separatingLine := resources at:'SEPARATING_LINE' default:false. "its so ugly"
    self is3D ifTrue:[
        self barHeight:(3 * ViewSpacing)
    ] ifFalse:[
        self barHeight:(2 * ViewSpacing)
    ].
    barWidth := 2 * ViewSpacing. "motif style width"
!

initCursor
    "set the cursor - a double arrow"

    "which one looks better ?"
    cursor := Cursor upDownArrow
    "cursor := Cursor upLimitArrow"
!

initEvents
    self enableButtonEvents.
    self enableButtonMotionEvents
!

fixSize 
    extentChanged ifTrue:[
        super fixSize.
        self resizeSubviewsFrom:1 to:(subViews size)
    ] ifFalse:[
        super fixSize
    ]
! !

!VariableVerticalPanel methodsFor:'accessing'!

add:aView
    "a view is added; make its size relative (if not already done)"

"obsolete" self halt.

    super add:aView.
    shown ifTrue:[
        (superView isNil or:[superView shown]) ifTrue:[
            self setupSubviewSizes
        ]
    ]
!

removeSubView:aView
    "a view is removed; adjust other subviews sizes"

    super removeSubView:aView.
    shown ifTrue:[
        (superView isNil or:[superView shown]) ifTrue:[
            self setupSubviewSizes
        ]
    ]
!

barHeight:nPixel
    "set the height of the separating bar"

    barHeight := nPixel.

    "if screen is very low-res, make certain bar is visible and catchable"
    (barHeight < 4) ifTrue:[
        barHeight := 4
    ].

    "make it even so spacing is equally spreadable among subviews"
    barHeight odd ifTrue:[
        barHeight := barHeight + 1
    ]
!

handlePosition:aSymbol
    "define the position of the handle; the argument aSymbol
     may be one of #left, #right or #center"

    handlePosition := aSymbol
!

handlePosition
    "return the position of the handle"

    ^ handlePosition
!

style:styleSymbol
    "define the style of the handle;
     styleSymbol may be #motif to draw a little knob or
     enything else to draw scrollBars handleForm"

    (styleSymbol ~~ style) ifTrue:[
        style := styleSymbol.
        shadowForm := self class shadowFormOn:device.
        lightForm := self class lightFormOn:device.
        (self is3D and:[style ~~ #motif]) ifTrue:[
            shadowForm notNil ifTrue:[
                self barHeight:(shadowForm height + 2).
                barWidth := shadowForm width
            ]
        ].
        shown ifTrue:[
            self resizeSubviewsFrom:1 to:(subViews size).
            self redraw
        ]
    ]
! !

!VariableVerticalPanel methodsFor:'drawing'!

drawHandleFormAtX:hx y:hy
    "kludge for now"
    (viewBackground colorId notNil
     and:[shadowColor colorId notNil
          and:[lightColor colorId notNil]]) ifTrue:[
        self foreground:viewBackground background:noColor function:#xor.
        self displayOpaqueForm:shadowForm x:hx y:hy.
        self foreground:shadowColor function:#or.
        self displayOpaqueForm:shadowForm x:hx y:hy.
        self foreground:viewBackground function:#xor.
        self displayOpaqueForm:lightForm x:hx y:hy.
        self foreground:lightColor function:#or.
        self displayOpaqueForm:lightForm x:hx y:hy.

        self foreground:viewBackground.
        paint := nil. "kludge to force paint to be really set"
        self paint:viewBackground.
        self function:#copy
    ]
!

drawHandleAtX:hx y:hy
    |h y m|

    (self is3D and:[shadowForm notNil]) ifTrue:[
        h := shadowForm height
    ] ifFalse:[
        h := barHeight - 4
    ].

    self paint:viewBackground.
    self fillRectangleX:margin y:hy 
                  width:(width - margin - margin) 
                  height:barHeight.

    self is3D ifTrue:[
        m := (barHeight - h) // 2.
        shadowForm isNil ifTrue:[
            y := hy + (barHeight // 2).
            separatingLine ifTrue:[
                self paint:shadowColor.
                self displayLineFromX:margin y:y toX:(width - margin) y:y.
                y := y + 1.
                self paint:lightColor.
                self displayLineFromX:margin y:y toX:(width - margin) y:y.
            ].
            self paint:viewBackground.
            self fillRectangleX:(hx - barWidth) y:hy 
                         width:(barWidth + barWidth) 
                         height:h.

            self drawEdgesForX:(hx - barWidth)
                             y:(hy + m)
                         width:(barWidth + barWidth)
                        height:h level:2
        ] ifFalse:[
            self drawHandleFormAtX:hx y:(hy + m)
        ]
    ] ifFalse:[
        y := hy + barHeight - 1.
        self paint:handleColor.
        separatingLine ifTrue:[
            self displayLineFromX:0 y:hy+1 toX:width y:hy+1.
            self displayLineFromX:0 y:y toX:width y:y.
        ].
        self fillRectangleX:hx y:hy width:barHeight height:barHeight
    ]
!

redrawHandlesFrom:start to:stop
    "redraw some handles"

    subViews notNil ifTrue:[
        self handleOriginsFrom:start to:stop do:[:hPoint |
            self drawHandleAtX:(hPoint x) y:(hPoint y)
        ].
        movedHandle notNil ifTrue:[
            self noClipByChildren.
            self xoring:[
                self fillRectangleX:0 y:prev width:width height:barHeight
            ].
            self clipByChildren
        ]
    ]
!

redraw
    "redraw the handles"

    self redrawHandlesFrom:1 to:(subViews size)
! !

!VariableVerticalPanel methodsFor:'events'!

sizeChanged:how
    "tell subviews if I change size"

    shown ifTrue:[
        (how == #smaller) ifTrue:[
            self resizeSubviewsFrom:1 to:(subViews size)
        ] ifFalse:[
            self resizeSubviewsFrom:(subViews size) to:1
        ]
    ]
!

buttonPress:button x:bx y:by
    "button was pressed - if it hits a handle, start move"

    |handle|

    (button == 1) ifTrue:[
        handle := 1.
        self handleOriginsDo:[:hPoint |
            |hy|

            hy := hPoint y.
            (by between:hy and:(hy + barHeight)) ifTrue:[
                movedHandle := handle.
                prev := hy.
                start := by - hy.
                self noClipByChildren.
                self xoring:[
                    self fillRectangleX:0 y:hy width:width height:barHeight
                ].
                self clipByChildren.
                ^ self
            ].
            handle := handle + 1
        ].
        movedHandle := nil
    ] ifFalse:[
        super buttonPress:button x:bx y:by
    ]
!

buttonMotion:button x:bx y:by
    "mouse-button was moved while pressed;
     clear prev handleBar and draw handle bar at new position" 

    |ypos limitTop limitBot|

    movedHandle isNil ifTrue: [^ self].          "should not happen"

    "speedup - if there is already another movement, 
     ignore thisone ... "

    device synchronizeOutput.
    self buttonMotionEventPending ifTrue:[^ self].

    ypos := by - start.
    limitTop := barHeight // 2.
    limitBot := self height - barHeight.
    movedHandle > 1 ifTrue:[
        limitTop := (subViews at:movedHandle) origin y + (barHeight // 2)
    ].
    movedHandle < (subViews size - 1) ifTrue:[
        limitBot := (subViews at:(movedHandle + 2)) origin y - barHeight
    ].
    limitBot := limitBot - barHeight.
    (ypos < limitTop) ifTrue:[ "check against view limits"
        ypos := limitTop
    ] ifFalse:[
        (ypos > limitBot) ifTrue:[
            ypos := limitBot
        ]
    ].

    self noClipByChildren.
    self xoring:[
        self fillRectangleX:0 y:prev width:width height:barHeight.
        self fillRectangleX:0 y:ypos width:width height:barHeight
    ].
    self clipByChildren.
    prev := ypos
!

buttonRelease:button x:x y:y
    "end bar-move"

    |aboveView belowView aboveIndex belowIndex newY|

    (button == 1) ifTrue:[
        movedHandle isNil ifTrue:[^ self].

        "undo the last xor"

        self noClipByChildren.
        self xoring:[
            self fillRectangleX:0 y:prev width:width height:barHeight
        ].
        self clipByChildren.

        "compute the new relative heights"

        aboveIndex := movedHandle.
        belowIndex := movedHandle + 1.
        aboveView := subViews at:aboveIndex.
        belowView := subViews at:belowIndex.

        newY := (prev + start / height) asFloat.
        aboveView relativeCorner:aboveView relativeCorner x @ newY.
        belowView relativeOrigin:belowView relativeOrigin x @ newY.
        self resizeSubviewsFrom:aboveIndex to:belowIndex.

        movedHandle := nil.

        self redrawHandlesFrom:aboveIndex to:belowIndex
    ] ifFalse:[
        super buttonRelease:button x:x y:y
    ]
! !

!VariableVerticalPanel methodsFor:'private'!

anyNonRelativeSubviews
    "return true, if any of my subviews has no relative origin/extent"

    1 to:(subViews size) do:[:index |
        |view|

        view := subViews at:index.
        view relativeExtent isNil ifTrue:[^ true].
        view relativeOrigin isNil ifTrue:[^ true]
    ].
    ^ false
!

setupSubviewSizes
    "setup subviews sizes (in case of non-relative sizes)"

    |y h|

    self anyNonRelativeSubviews ifTrue:[
        "there is at least one subview without
         relative origin/extent - setup all subviews
         to spread evenly ..."

        y := 0.0.
        h := 1.0 / (subViews size).

        1 to:(subViews size) do:[:index |
            |view|

            view := subViews at:index.
            index == subViews size ifTrue:[
                view origin:(0.0 @ y) corner:(1.0 @ 1.0)
            ] ifFalse:[
                view origin:(0.0 @ y) corner:(1.0 @ (y + h))
            ].
            y := y + h
        ]
    ]
!

resizeSubviewsFrom:start to:stop
    "readjust size of some subviews"

    |step nSubviews|

    subViews notNil ifTrue:[
        (start <= stop) ifTrue:[
            step := 1
        ] ifFalse:[
            step := -1
        ].
        nSubviews := subViews size.
        start to:stop by:step do:[:index |
            |bw view o1 o2 relOrg relCorner newOrg newCorner|

            view := subViews at:index.
            bw := view borderWidth.

            index == 1 ifTrue:[
                o1 := 0.
            ] ifFalse:[
                o1 := barHeight // 2 - bw
            ].
            index ==  nSubviews ifTrue:[
                o2 := 0.
            ] ifFalse:[
                o2 := barHeight // 2 - bw
            ].

            relCorner := view relativeCorner.
            relCorner isNil ifTrue:[
                self error:'subview must have relative corner'
            ].
            newCorner := view cornerFromRelativeCorner.
            newCorner notNil ifTrue:[
                newCorner y:(newCorner y - o2)
            ].

            relOrg := view relativeOrigin.
            relOrg isNil ifTrue:[
                self error:'subview must have relative origin'
            ].
            newOrg := view originFromRelativeOrigin.
            newOrg notNil ifTrue:[
                (index ~~ 1) ifTrue:[  
                    newOrg y:(newOrg y + o1)
                ].
            ].
            view pixelOrigin:newOrg corner:newCorner
        ]
    ]
!

handleOriginsFrom:start to:stop do:aBlock
    "evaluate the argument block for some handle-origins"

    |x hw|

    subViews notNil ifTrue:[
        shadowForm notNil ifTrue:[
            hw := shadowForm width
        ] ifFalse:[
            hw := barHeight
        ].
        (handlePosition == #left) ifTrue:[
            x := hw * 2
        ] ifFalse:[
            (handlePosition == #right) ifTrue:[
                x := width - (2 * hw) - margin
            ] ifFalse:[
                x := width // 2
            ]
        ].
        (start + 1) to:stop do:[:index |
            |view y|

            view := subViews at:index.
            y := view origin y - barHeight + 1.
            aBlock value:(x @ y)
        ]
    ]
!

handleOriginsDo:aBlock
    "evaluate the argument block for every handle-origin"

    self handleOriginsFrom:1 to:(subViews size) do:aBlock
! !