VariableHorizontalPanel.st
author claus
Wed, 13 Oct 1993 02:04:14 +0100
changeset 3 9d7eefb5e69f
parent 0 e6a541c1c0eb
child 5 7b4fb1b170e5
permissions -rw-r--r--
(none)

"
 COPYRIGHT (c) 1992-93 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.
"

VariableVerticalPanel subclass:#VariableHorizontalPanel
         instanceVariableNames:''
         classVariableNames:'hArrow'
         poolDictionaries:''
         category:'Views-Layout'
!

VariableHorizontalPanel comment:'

COPYRIGHT (c) 1992-93 by Claus Gittinger
              All Rights Reserved

a View to separate its subviews horizontally by a movable bar
to adjust the size-ratios.
The bar-handle is either an exposed knob (knobStyle == #motif)
or the forms defined in Scroller (knobStyle ~~ #motif)

$Header: /cvs/stx/stx/libwidg/VariableHorizontalPanel.st,v 1.2 1993-10-13 01:03:58 claus Exp $

written summer 92 by claus
'!

!VariableHorizontalPanel methodsFor:'initializing'!

initCursor
    "set the cursor - a horizontal double arrow"

    "which one looks better ?"
    cursor := Cursor leftRightArrow
    "cursor := Cursor leftLimitArrow"
! !

!VariableHorizontalPanel methodsFor:'private'!

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

    |y hh|

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

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

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

    |x w |

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

        x := 0.0.
        w := 1.0 / (subViews size).

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

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

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 relCorner relOrg newCorner newOrg|

            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 x:(newCorner x - o2)
            ].

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

!VariableHorizontalPanel methodsFor:'events'!

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 |
            |hx|

            hx := hPoint x.
            (bx between:hx and:(hx + barHeight)) ifTrue:[
                movedHandle := handle.
                prev := hx.
                start := bx - hx.
                self noClipByChildren.
                self xoring:[
                    self fillRectangleX:hx y:0 width:barHeight height:height
                ].
                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" 

    |xpos limitTop limitBot|

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

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

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

    xpos := bx - start.
    limitTop := barHeight // 2.
    limitBot := self width - barHeight.
    movedHandle > 1 ifTrue:[
        limitTop := (subViews at:movedHandle) origin x + (barHeight // 2)
    ].
    movedHandle < (subViews size - 1) ifTrue:[
        limitBot := (subViews at:(movedHandle + 2)) origin x - barHeight
    ].
    limitBot := limitBot - barHeight.
    (xpos < limitTop) ifTrue:[ "check against view limits"
        xpos := limitTop
    ] ifFalse:[
        (xpos > limitBot) ifTrue:[
            xpos := limitBot
        ]
    ].

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

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

    |aboveView belowView aboveIndex belowIndex newX|

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

        "undo the last xor"

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

        "compute the new relative heights"

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

        newX := (prev + start / width) asFloat .
        aboveView relativeCorner:newX @ aboveView relativeCorner y.
        belowView relativeOrigin:newX @ belowView relativeOrigin y.
        self resizeSubviewsFrom:aboveIndex to:belowIndex.

        movedHandle := nil.

        "and redraw handles"

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

!VariableHorizontalPanel methodsFor:'drawing'!

drawHandleAtX:hx y:hy
    |w x m|

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

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

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

            self drawEdgesForX:(hx + m)
                             y:(hy - barWidth)
                         width:w height:(barWidth + barWidth)
                         level:2
        ] ifFalse:[
            self drawHandleFormAtX:(hx + m) y:hy
        ]
    ] ifFalse:[
        x := hx + barHeight - 2.
        self paint:handleColor.
        self displayLineFromX:hx y:0 toX:hx y:height.
        self displayLineFromX:x y:0 toX:x y:height.
        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:prev y:0 width:barHeight height:height
            ].
            self clipByChildren
        ]
    ]

! !