VariablePanel.st
author Claus Gittinger <cg@exept.de>
Thu, 04 Jun 1998 18:41:02 +0200
changeset 1550 f0297a144983
parent 1529 509edab0a08b
child 1551 1b9a8a925fe7
permissions -rw-r--r--
clear view when resizing

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

SimpleView subclass:#VariablePanel
	instanceVariableNames:'barHeight barWidth separatingLine shadowForm lightForm showHandle
		handlePosition handleColor handleStyle handleLevel noColor
		trackLine redrawLocked orientation handleLabels knobHeight'
	classVariableNames:'DefaultShowHandle DefaultHandleStyle DefaultHandlePosition
		DefaultTrackingLine DefaultSeparatingLine DefaultHandleColor
		DefaultHandleLevel DefaultVCursor DefaultHCursor
		DefaultHandleImage'
	poolDictionaries:''
	category:'Views-Layout'
!

!VariablePanel class methodsFor:'documentation'!

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

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

    In order to correctly setup this kind of view, the subviews must
    be created with a relative origin & relative corner.
    The panel does not verify the relative subview bounds; 
    therefore, it is your responsibility to set those relative sizes to fit
    according the orientation (see bad example below).

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

    Typically creation is done as:

        p := VariablePanel in:superView.
        p orientation:#vertical.

        v1 := <someViewClass> origin:0.0 @ 0.0
                              corner:1.0 @ 0.5
                                  in:p.
        v2 := <someViewClass> origin:0.0 @ 0.5 
                              corner:1.0 @ 0.8 
                                  in:p.
        v3 := <someViewClass> origin:0.0 @ 0.8 
                              corner:1.0 @ 1.0
                                  in:p.

    The two subclasses VariableHorizontalPanel and VariableVerticalPanel
    preset the orientation. They are a kept for backward compatibility
    (in previous versions, there used to be no common VariablePanel (super-) class).

    Notice: if it is required to insert a fixed-size view in the panel,
    use an extra view & insets, and place the subview into that extra view.
    See examples.

    [instance Variables:]

        barHeight               <Integer>       the height of the bar (for verticalPanels)
        barWidth                <Integer>       the width of the bar  (for horizontalPanels)

        separatingLine          <Boolean>       show a separating line (as in motif style)

        shadowForm              <Image/Form>    form (shadow part) drawn as handle - if nonNil

        lightForm               <Image/Form>    form (light part) drawn as handle - if nonNil

        showHandle              <Boolean>       if false, no handle is drawn

        handlePosition          <Symbol>        where is the handle - one of #left, #center, #right

        handleColor             <Color>         inside color of handle - defaults to viewBackground

        handleStyle             <Symbol>        type of handle; one of #next, #motif or nil

        handleLevel             <Integer>       3D level of handle (only valid if no form is given)

        trackLine               <Boolean>       if true, an inverted line is drawn for tracking;
                                                otherwise, the whole bar is inverted.

        redrawLocked                            internal - locks redraws while tracking

        orientation             <Symbol>        one of #horizontal / #vertical


    [styleSheet values:]
        variablePanel.showHandle        true/false - should a handle be shown (default:true)

        variablePanel.handleStyle       #next / #motif / #iris / #full / nil (special handles)

        variablePanel.handlePosition    #left / #center / #right (default:#right)

        variablePanel.handleLevel       3D level of heandle (default:2)

        variablePanel.trackingLine      when moved, track an inverted line (as in motif)
                                        as opposed to tracking the whole bar (default:false)
                                        (obsoleted by trackingStyle)

        variablePanel.trackingStyle     #solidRectangle / #solidLine / #dashedLine
                                        detailed control over how to draw tracking
                                        (obsoletes trackingLine above)

        variablePanel.separatingLine    draw a separating line in the bar as in motif (default:false)

        variablePanel.handleColor       color of the handle. (default:Black)

        variablePanel.handleEnteredColor 
                                        color of the handle when the pointer is in the bar (default:nil)

    [see also:]
        PanelView
        
    [author:]
        Claus Gittinger
"
!

examples
"
   example (notice that the subviews MUST have relative bounds):
                                                                        [exBegin]
        |top p v1 v2 v3|

        top := StandardSystemView new.
        top extent:300@300.

        p := VariablePanel 
                 origin:0.0 @ 0.0
                 corner:1.0 @ 1.0
                 in:top.
        p orientation:#vertical.

        v1 := View origin:0.0@0.0 corner:1.0@(1/2) in:p.
        v2 := View origin:0.0@(1/2) corner:1.0@(2/3) in:p.
        v3 := View origin:0.0@(2/3) corner:1.0@1.0 in:p.

        v1 viewBackground:(Color red).
        v2 viewBackground:(Color green).
        v3 viewBackground:(Color yellow).

        top open
                                                                        [exEnd]



   change the handles level:
                                                                        [exBegin]
        |top p v1 v2 v3|

        top := StandardSystemView new.
        top extent:300@300.

        p := VariablePanel 
                 origin:0.0 @ 0.0
                 corner:1.0 @ 1.0
                 in:top.
        p orientation:#vertical.
        p handleLevel:-1.

        v1 := View origin:0.0@0.0 corner:1.0@(1/3) in:p.
        v2 := View origin:0.0@(1/3) corner:1.0@(2/3) in:p.
        v3 := View origin:0.0@(2/3) corner:1.0@1.0 in:p.

        v1 viewBackground:(Color red).
        v2 viewBackground:(Color green).
        v3 viewBackground:(Color yellow).

        top open
                                                                        [exEnd]



   change the handles style to nil makes it invisible:
                                                                        [exBegin]
        |top p v1 v2 v3|

        top := StandardSystemView new.
        top extent:300@300.

        p := VariablePanel 
                 origin:0.0 @ 0.0
                 corner:1.0 @ 1.0
                 in:top.
        p orientation:#vertical.
        p handleStyle:nil.

        v1 := View origin:0.0@0.0 corner:1.0@(1/3) in:p.
        v2 := View origin:0.0@(1/3) corner:1.0@(2/3) in:p.
        v3 := View origin:0.0@(2/3) corner:1.0@1.0 in:p.

        v1 viewBackground:(Color red).
        v2 viewBackground:(Color green).
        v3 viewBackground:(Color yellow).

        top open
                                                                        [exEnd]



   define your own handle (-bitmap):
                                                                        [exBegin]
        |top p v1 v2 v3|

        top := StandardSystemView new.
        top extent:300@300.

        p := VariablePanel 
                 origin:0.0 @ 0.0
                 corner:1.0 @ 1.0
                 in:top.
        p orientation:#vertical.
        p handleImage:(Image fromFile:'bitmaps/ScrollLt.8.xbm').

        v1 := View origin:0.0@0.0 corner:1.0@(1/3) in:p.
        v2 := View origin:0.0@(1/3) corner:1.0@(2/3) in:p.
        v3 := View origin:0.0@(2/3) corner:1.0@1.0 in:p.

        v1 viewBackground:(Color red).
        v2 viewBackground:(Color green).
        v3 viewBackground:(Color yellow).

        top open
                                                                        [exEnd]



   another handle-bitmap:
                                                                        [exBegin]
        |top p v1 v2 v3|

        top := StandardSystemView new.
        top extent:300@300.

        p := VariablePanel 
                 origin:0.0 @ 0.0
                 corner:1.0 @ 1.0
                 in:top.
        p orientation:#vertical.
        p handleImage:(Form width:9
                            height:11
                            fromArray:#(
                                        2r00000000 2r00000000
                                        2r00001000 2r00000000
                                        2r00011100 2r00000000
                                        2r00111110 2r00000000
                                        2r01111111 2r00000000
                                        2r00000000 2r00000000
                                        2r01111111 2r00000000
                                        2r00111110 2r00000000
                                        2r00011100 2r00000000
                                        2r00001000 2r00000000
                                        2r00000000 2r00000000
                                       )
                      ).

        v1 := View origin:0.0@0.0 corner:1.0@(1/3) in:p.
        v2 := View origin:0.0@(1/3) corner:1.0@(2/3) in:p.
        v3 := View origin:0.0@(2/3) corner:1.0@1.0 in:p.

        v1 viewBackground:(Color red).
        v2 viewBackground:(Color green).
        v3 viewBackground:(Color yellow).

        top open
                                                                        [exEnd]

    placing scrolled and unscrolled views into a variablePanel:
                                                                        [exBegin]
        |top p v1 v2 v3|

        top := StandardSystemView new.
        top extent:300@300.

        p := VariablePanel 
                 origin:0.0 @ 0.0
                 corner:1.0 @ 1.0
                 in:top.
        p orientation:#vertical.

        v1 := ScrollableView for:SelectionInListView in:p.
        v1 origin:0.0 @ 0.0 corner:1.0 @ 0.5.
        v1 list:(FileDirectory directoryNamed:'/etc') contents.
        v1 action:[:selNr |
                |fullName stream text|
                fullName := '/etc/' , v1 selectionValue.
                stream := fullName asFilename readStream.
                stream notNil ifTrue:[
                    text := stream contents.
                    v2 contents:text.
                    v3 contents:text
                ]
        ].

        v2 := TextView origin:0.0 @ 0.5 corner:1.0 @ 0.8 in:p.

        v3 := ScrollableView for:TextView in:p.
        v3 origin:0.0 @ 0.8 corner:1.0 @ 1.0.
        top open
                                                                        [exEnd]


    dynamically adding/removing views:
                                                                        [exBegin]
        |top p v1 v2 b|

        top := StandardSystemView new.
        top extent:300@300.

        b := Toggle label:'show' in:top.
        b showLamp:false.
        b origin:0.0 @ 0.0 corner:(1.0 @ 40).
        b action:[:state |
                state ifTrue:[
                    b label:'hide'.
                    v1 origin:0.0 @ 0.0 corner:1.0 @ 0.5.
                    v2 := ScrollableView for:EditTextView.
                    v2 origin:0.0 @ 0.5 corner:1.0 @ 1.0.
                    v2 contents:'another text'.
                    p addSubView:v2.
                    v2 realize.
                ] ifFalse:[
                    b label:'show'.
                    v2 destroy.
                    v1 origin:0.0 @ 0.0 corner:1.0 @ 1.0
                ]
            ].

        p := VariablePanel
                origin:0.0 @ 0.0
                corner:1.0 @ 1.0
                in:top.
        p orientation:#vertical.
        p topInset:50.

        v1 := ScrollableView for:EditTextView in:p.
        v1 origin:0.0 @ 0.0 corner:1.0 @ 1.0.
        v1 contents:'some text'.

        top open
                                                                        [exEnd]


    dynamically flipping orientation:
    Notice: you have to change the relative bounds of the subviews first.
                                                                        [exBegin]
        |top p v1 v2 b|

        top := StandardSystemView new.
        top extent:300@300.

        b := Toggle label:'flip' in:top.
        b showLamp:false.
        b origin:0.0 @ 0.0 corner:(1.0 @ 40).
        b action:[:state |
                state ifTrue:[
                    v1 origin:0.0 @ 0.0 corner:0.5 @ 1.0.
                    v2 origin:0.5 @ 0.0 corner:1.0 @ 1.0.
                    p orientation:#horizontal.
                ] ifFalse:[
                    v1 origin:0.0 @ 0.0 corner:1.0 @ 0.5.
                    v2 origin:0.0 @ 0.5 corner:1.0 @ 1.0.
                    p orientation:#vertical.
                ].
            ].

        p := VariablePanel
                origin:0.0 @ 0.0
                corner:1.0 @ 1.0
                in:top.
        p orientation:#vertical.
        p topInset:50.

        v1 := ScrollableView for:EditTextView in:p.
        v1 origin:0.0 @ 0.0 corner:1.0 @ 0.5.
        v1 contents:'some text'.

        v2 := ScrollableView for:EditTextView in:p.
        v2 origin:0.0 @ 0.5 corner:1.0 @ 1.0.
        v2 contents:'another text'.

        top open
                                                                        [exEnd]


   combining fix-size with variable size:
   (need 3 extra frame-views to place the extra labels into)
                                                                        [exBegin]
        |top p v1 l1 v2 l2 v3 l3 f1 f2 f3|

        top := StandardSystemView new.
        top extent:300@300.

        p := VariablePanel 
                 origin:0.0 @ 0.0
                 corner:1.0 @ 1.0
                 in:top.

        p orientation:#vertical.

        f1 := View origin:0.0@0.0 corner:1.0@0.3 in:p.
        f2 := View origin:0.0@0.3 corner:1.0@0.6 in:p.
        f3 := View origin:0.0@0.6 corner:1.0@1.0 in:p.

        v1 := View origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:f1.
        v2 := View origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:f2.
        v3 := View origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:f3.

        l1 := Label label:'sub1' in:f1.
        l2 := Label label:'sub2' in:f2.
        l3 := Label label:'sub3' in:f3.

        l1 origin:0.0 @ 0.0 corner:1.0 @ 0.0 ; 
           bottomInset:(l1 preferredExtent y negated).
        l2 origin:0.0 @ 0.0 corner:1.0 @ 0.0 ; 
           bottomInset:(l2 preferredExtent y negated).
        l3 origin:0.0 @ 0.0 corner:1.0 @ 0.0 ; 
           bottomInset:(l3 preferredExtent y negated).

        v1 topInset:(l1 preferredExtent y); level:-1.
        v2 topInset:(l2 preferredExtent y); level:-1.
        v3 topInset:(l3 preferredExtent y); level:-1.

        v1 viewBackground:(Color red).
        v2 viewBackground:(Color green).
        v3 viewBackground:(Color yellow).

        top open
                                                                        [exEnd]

   VerticalPansels allow a label to be associated with the
   handles; this looks much like the above, but is slightly
   more compact. Notice, no label can be placed above the first 
   view - it has no handle.
                                                                        [exBegin]
        |top p v1 v2 v3|

        top := StandardSystemView new.
        top extent:300@300.

        p := VariablePanel 
                 origin:0.0 @ 0.0
                 corner:1.0 @ 1.0
                 in:top.

        p orientation:#vertical.
        p handleLabels:#('ignored' 'sub2' 'sub3').

        v1 := View origin:0.0@0.0 corner:1.0@0.3 in:p.
        v2 := View origin:0.0@0.3 corner:1.0@0.6 in:p.
        v3 := View origin:0.0@0.6 corner:1.0@1.0 in:p.

        v1 viewBackground:(Color red).
        v2 viewBackground:(Color green).
        v3 viewBackground:(Color yellow).

        top open
                                                                        [exEnd]

   handle labels can be more than strings ....
   (however, they should have about the same height, since
    the largest defines heights of all bars;
    retry the example below with a larger bitmap image ...)
                                                                        [exBegin]
        |top e p v1 v2 v3|

        top := StandardSystemView new.
        top extent:300@300.

        p := VariablePanel 
                 origin:0.0 @ 0.0
                 corner:1.0 @ 1.0
                 in:top.

        p orientation:#vertical.
        e := Array with:#bold
                   with:#color->Color red.

        p handleLabels:(Array with:nil
                              with:('bold and red' asText emphasizeAllWith:e)
                              with:(Image fromFile:'ScrollRt.xbm')).

        v1 := View origin:0.0@0.0 corner:1.0@0.3 in:p.
        v2 := View origin:0.0@0.3 corner:1.0@0.6 in:p.
        v3 := View origin:0.0@0.6 corner:1.0@1.0 in:p.

        v1 viewBackground:(Color red).
        v2 viewBackground:(Color green).
        v3 viewBackground:(Color yellow).

        top open
                                                                        [exEnd]



   BAD EXAMPLE (wrong relative sizes - repaired on handle move):
                                                                        [exBegin]
        |top p v1 v2 v3|

        top := StandardSystemView new.
        top extent:300@300.

        p := VariablePanel 
                 origin:0.0 @ 0.0
                 corner:1.0 @ 1.0
                 in:top.
        p orientation:#vertical.

        v1 := View origin:0.0 @ 0.0   corner:1.0 @ (1/4) in:p.
        v2 := View origin:0.0 @ (1/2) corner:1.0 @ (3/4) in:p.
        v3 := View origin:0.0 @ (3/4) corner:1.0 @ 1.0   in:p.

        v1 viewBackground:(Color red).
        v2 viewBackground:(Color green).
        v3 viewBackground:(Color yellow).

        top open
                                                                        [exEnd]
"
! !

!VariablePanel class methodsFor:'defaults'!

cursorForOrientation:orientation
    "return an appropriate cursor"

    |cursor|

    orientation == #vertical ifTrue:[
        DefaultVCursor notNil ifTrue:[
            cursor := DefaultVCursor
        ] ifFalse:[
            cursor := Cursor 
                        sourceForm:(Image fromFile:'bitmaps/VVPanel.xbm')
                        maskForm:(Image fromFile:'bitmaps/VVPanel_m.xbm')
                        hotX:8
                        hotY:8.
            "
             if bitmaps are not available, use a standard cursor
            "
            cursor isNil ifTrue:[
                "which one looks better ?"
                cursor := Cursor upDownArrow
                "cursor := Cursor upLimitArrow"
            ].
            DefaultVCursor := cursor
        ]
    ] ifFalse:[
        DefaultHCursor notNil ifTrue:[
            cursor := DefaultHCursor
        ] ifFalse:[
            cursor := Cursor 
                        sourceForm:(Image fromFile:'bitmaps/VHPanel.xbm')
                        maskForm:(Image fromFile:'bitmaps/VHPanel_m.xbm')
                        hotX:8
                        hotY:8.
            "
             if bitmaps are not available, use a standard cursor
            "
            cursor isNil ifTrue:[
                "which one looks better ?"
                cursor := Cursor leftRightArrow
                "cursor := Cursor leftLimitArrow"
            ].
            DefaultHCursor := cursor
        ]
    ].

    ^ cursor

    "Created: 28.3.1997 / 13:40:01 / cg"
    "Modified: 28.3.1997 / 14:45:29 / cg"
!

lightFormOn:aDisplay
    "use same handle as Scroller"

    ^ Scroller handleLightFormOn:aDisplay
!

shadowFormOn:aDisplay
    "use same handle as Scroller"

    ^ Scroller handleShadowFormOn:aDisplay
!

updateStyleCache
    "extract values from the styleSheet and cache them in class variables"

    <resource: #style (#'variablePanel.showHandle' 
                       #'variablePanel.handleStyle'
                       #'variablePanel.handleImage'
                       #'variablePanel.handlePosition' 
                       #'variablePanel.handleLevel'
                       #'variablePanel.trackingLine'   
                       #'variablePanel.trackingStyle'
                       #'variablePanel.separatingLine' 
                       #'variablePanel.handleColor')>

    |lineModeBoolean|

    DefaultShowHandle := StyleSheet at:'variablePanel.showHandle' default:true.
    DefaultHandleStyle := StyleSheet at:'variablePanel.handleStyle'.
    DefaultHandlePosition := StyleSheet at:'variablePanel.handlePosition' "default:#right".
    DefaultHandlePosition isNil ifTrue:[
        DefaultHandlePosition := ScrollableView defaultScrollBarPosition.
    ].
    DefaultHandleLevel := StyleSheet at:'variablePanel.handleLevel' default:2.
    DefaultTrackingLine := StyleSheet at:'variablePanel.trackingStyle'.
    DefaultTrackingLine isNil ifTrue:[
        lineModeBoolean := StyleSheet at:'variablePanel.trackingLine' default:false.
        lineModeBoolean ifTrue:[
            DefaultTrackingLine := #solidLine
        ] ifFalse:[
            DefaultTrackingLine := #solidRectangle
        ]
    ].

    DefaultSeparatingLine := StyleSheet at:'variablePanel.separatingLine' default:false.
    DefaultHandleColor := StyleSheet colorAt:'variablePanel.handleColor' default:Black.

    DefaultHandleImage := StyleSheet at:'variablePanel.handleImage'

    "
     VariablePanel updateStyleCache
    "

    "Modified: / 19.5.1998 / 16:08:54 / cg"
! !

!VariablePanel methodsFor:'accessing'!

addSubView:aView
    "a view is added; adjust other subviews sizes"

    super addSubView:aView.

"/    (aView relativeOrigin isNil 
"/    or:[aView relativeExtent isNil and:[aView relativeCorner isNil]]) ifTrue:[
"/        aView geometryLayout:nil.
"/        aView origin:0.0@0.0.
"/        aView extent:1.0@0.5.
"/        self setupSubviews
"/    ].

    realized ifTrue:[
        self resizeSubviews.
    ]

    "Created: 17.1.1996 / 22:41:00 / cg"
    "Modified: 24.2.1996 / 19:05:05 / cg"
!

orientation
    "return my orientation; either #horizontal or #vertical"

    ^ orientation

    "Modified: 6.3.1996 / 18:08:45 / cg"
!

orientation:aSymbol
    "change  my orientation; aSymbol must be one of #horizontal or #vertical.
     Changing implies a resize of my subViews."

    aSymbol ~~ orientation ifTrue:[
        orientation := aSymbol.
        self initCursor.
        self anyNonRelativeSubviews ifTrue:[
            self setupSubviews
        ].
        shown ifTrue:[
            self cursor:cursor.
            self sizeChanged:nil.
            self invalidate.
        ]
    ]

    "Modified: 29.5.1996 / 16:22:35 / cg"
!

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

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

!VariablePanel methodsFor:'accessing-look'!

barHeight
    "return the height of the separating bar"

    ^ barHeight
!

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

    barHeight := nPixel.

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

    "Modified: 7.11.1996 / 20:07:11 / cg"
    "Modified: 28.4.1997 / 14:30:33 / dq"
!

handleImage:aBitmapOrImage
    "define the handles image"

    shadowForm := aBitmapOrImage.
    lightForm := nil.
    self computeBarHeight.

    "Created: 7.11.1996 / 20:21:10 / cg"
    "Modified: 7.11.1996 / 20:27:22 / cg"
!

handleLabels:aCollectionOfLabels
    orientation == #horizontal ifTrue:[
        self error:'not allowed for horizontal panels'
    ].

    handleLabels := aCollectionOfLabels.
    self computeBarHeight.
    self resizeSubviews.

!

handleLevel:aNumber
    "define the 3D level of the handle (only with some styles).
     Normally, this is defined via styleSheet files, but this entry allows
     individual views to be manipulated."

    handleLevel := aNumber
!

handlePosition
    "return the position of the handle"

    ^ handlePosition
!

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

    handlePosition := aSymbol
!

handleShadowImage:shadowImage lightImage:lightImage
    "define the handles image; both shadow and light parts"

    shadowForm := shadowImage.
    lightForm := lightImage.
    self computeBarHeight.

    "Created: 7.11.1996 / 20:21:51 / cg"
    "Modified: 7.11.1996 / 20:27:26 / cg"
!

handleStyle:styleSymbol
    "define the style of the handle;
     styleSymbol may be #motif to draw a little knob or
     anything else to draw scrollBars handleForm.
     Normally, this is defined via styleSheet files, but this entry allows
     individual views to be manipulated."

    (styleSymbol ~~ handleStyle) ifTrue:[
        handleStyle := styleSymbol.
        handleStyle == #next ifTrue:[
            shadowForm := self class shadowFormOn:device.
            lightForm := self class lightFormOn:device.
        ] ifFalse:[
            shadowForm := lightForm := nil
        ].

        shadowForm notNil ifTrue:[
            (self is3D and:[handleStyle ~~ #motif]) ifTrue:[
                self barHeight:(shadowForm height + 2).
                barWidth := shadowForm width
            ]
        ].
        shown ifTrue:[
            self resizeSubviews.
            self invalidate
        ]
    ]

    "Created: 24.2.1996 / 19:04:07 / cg"
    "Modified: 29.5.1996 / 16:22:24 / cg"
!

style:styleSymbol
    "define the style of the handle;
     styleSymbol may be #motif to draw a little knob or
     anything else to draw scrollBars handleForm.
     Normally, this is defined via styleSheet files, but this entry allows
     individual views to be manipulated."

    self handleStyle:styleSymbol

    "Modified: 24.2.1996 / 19:04:19 / cg"
! !

!VariablePanel methodsFor:'drawing'!

drawHandle:hIndex atX:hx y:hy
    "draw a single handle at hx/hy"

    |h w x y m lbl maxKnob
     mar           "{ Class: SmallInteger }"
     barWidthInt   "{ Class: SmallInteger }"
     barHeightInt  "{ Class: SmallInteger }" |

    (handleStyle isNil 
    or:[handleStyle == #none]) ifTrue:[^ self].

    mar := margin.
    barHeightInt := barHeight.
    barWidthInt := barWidth.

    shadowForm notNil ifTrue:[
        h := shadowForm height.
        w := shadowForm width .
        maxKnob := h min:barHeightInt.
    ] ifFalse:[
        maxKnob := knobHeight min: barHeightInt.
        maxKnob := maxKnob max:4.
        w := h := maxKnob - 4.
    ].

    self paint:viewBackground.
    self lineStyle:#solid.

    orientation == #vertical ifTrue:[
        self fillRectangleX:mar y:hy 
                      width:(width - mar - mar) 
                     height:barHeightInt.

        (handleStyle ~~ #normal and:[handleStyle ~~ #mswindows]) ifTrue:[
            m := (maxKnob - h) // 2.

            shadowForm isNil ifTrue:[

                y := hy + (barHeightInt // 2).   "/ center of the bar

                separatingLine ifTrue:[
                    self paint:shadowColor.
                    self displayLineFromX:mar y:y toX:(width - mar) y:y.
                    y := y + 1.
                    self paint:lightColor.
                    self displayLineFromX:mar y:y toX:(width - mar) y:y.
                ].
                self paint:viewBackground.

                self fillRectangleX:(hx - barWidthInt) y:hy 
                             width:(barWidthInt + barWidthInt) 
                             height:h.

                handleStyle == #line ifTrue:[
                    self paint:handleColor.
                    self displayLineFromX:hx - barWidthInt y:y toX:hx + barWidthInt y:y
                ] ifFalse:[
                    y := hy.   
                    handleStyle == #st80 ifTrue:[
                        y := y - 1
                    ].

                    handleStyle == #full ifTrue:[
                        self drawEdgesForX:0-handleLevel
                                         y:(y + m)
                                     width:width+handleLevel+handleLevel
                                    height:h 
                                     level:handleLevel.
                    ] ifFalse:[
                        self drawEdgesForX:(hx - barWidthInt)
                                         y:(y + m)
                                     width:(barWidthInt + barWidthInt)
                                    height:h 
                                     level:handleLevel.

                        handleStyle == #iris ifTrue:[
                            self paint:handleColor.
                            self fillDeviceRectangleX:(hx - barWidthInt + 2)
                                                    y:(y + m + 2)
                                                width:(barWidthInt + barWidthInt - 4)
                                               height:h - 4
                        ]
                    ]
                ].
            ] ifFalse:[
                y := hy.
                self drawHandleFormAtX:hx y:(y + m)
            ].

            handleStyle == #st80 ifTrue:[
                y := hy - 1.
                self paint:lightColor.
                self displayLineFromX:mar y:y toX:(width - mar - mar - 1) y:y.
                self displayLineFromX:0 y:hy toX:0 y:(hy + knobHeight - 1).
                y := hy + knobHeight - 2.
                self paint:shadowColor.
                self displayLineFromX:mar y:y toX:(width - mar) y:y.
                    "uncomment the -1 if you dont like the notch at the right end"
                    "                            VVV"
                self displayLineFromX:width-1 y:hy" "-1" " toX:width-1 y:(hy + knobHeight - 1 - 1).
            ].
        ] ifFalse:[
            y := hy + barHeightInt - 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:barWidthInt height:barHeightInt
        ].

        lbl := self handleLabelAt:hIndex.
        lbl notNil ifTrue:[
            hIndex ~~ 1 ifTrue:[
                self paint:Color black.
                lbl isImageOrForm ifTrue:[
                    lbl displayOn:self x:mar y:hy
                ] ifFalse:[
                    lbl displayOn:self x:mar y:hy + font ascent + 1
                ]
            ]
        ].

    ] ifFalse:[
        self fillRectangleX:hx y:mar 
                      width:barHeightInt
                     height:(height - mar - mar).

        (handleStyle ~~ #normal and:[handleStyle ~~ #mswindows]) ifTrue:[
             m := (barHeightInt - w) // 2.
             shadowForm isNil ifTrue:[
                x := hx + (barHeightInt // 2).
                separatingLine ifTrue:[
                    self paint:shadowColor.
                    self displayLineFromX:x y:mar toX:x y:(height - mar).
                    x := x + 1.
                    self paint:lightColor.
                    self displayLineFromX:x y:mar toX:x y:(height - mar).
                ].
                self paint:viewBackground.
                self fillRectangleX:hx y:(hy - barWidthInt) 
                              width:w 
                             height:(barWidthInt + barWidthInt).

                handleStyle == #line ifTrue:[
                    self paint:handleColor.
                    self displayLineFromX:x y:hy - barWidthInt toX:x y:hy + barWidthInt.
                ] ifFalse:[
                    x := hx.
                    handleStyle == #st80 ifTrue:[
                        x := x - 1.
                    ].
                    handleStyle == #full ifTrue:[
                        self drawEdgesForX:(x + m)
                                         y:0-handleLevel
                                     width:w
                                    height:height+handleLevel+handleLevel 
                                     level:handleLevel.
                    ] ifFalse:[
                        self drawEdgesForX:(x + m)
                                         y:(hy - barWidthInt)
                                     width:w 
                                    height:(barWidthInt + barWidthInt)
                                     level:handleLevel.
                        handleStyle == #iris ifTrue:[
                            self paint:handleColor.
                            self fillDeviceRectangleX:(x + m + 2)
                                                    y:(hy - barWidthInt + 2)
                                                width:w - 4
                                               height:(barWidthInt + barWidthInt - 4)
                        ].
                    ].
                ]
            ] ifFalse:[
                x := hx.
                self drawHandleFormAtX:(x + m) y:hy
            ].
            handleStyle == #st80 ifTrue:[
                x := hx - 1.
                self paint:lightColor.
                self displayLineFromX:x y:mar toX:x y:(height - mar).
                self displayLineFromX:hx y:0 toX:(hx + barHeightInt - 1) y:0.
                x := hx + barHeightInt - 2.
                self paint:shadowColor.
                self displayLineFromX:x y:mar toX:x y:(height - mar).
                    "uncomment the -1 if you dont like the notch at the bottom end"
                    "                   VVV"
                self displayLineFromX:hx" "-1" " y:height-1 toX:(hx + barHeightInt - 1) y:height-1.
            ].
        ] ifFalse:[
            x := hx + barHeightInt - 1.
            self paint:handleColor.
            separatingLine ifTrue:[
                self displayLineFromX:hx+1 y:0 toX:hx+1 y:height.
                self displayLineFromX:x y:0 toX:x y:height.
            ].
            self fillRectangleX:hx y:hy width:barHeightInt height:barWidthInt
        ]
    ].

    "Modified: / 1.11.1997 / 11:55:05 / cg"
!

drawHandleFormAtX:hx y:hy
    "draw a handles bitmap at hx/hy"

    shadowForm notNil ifTrue:[
        self paint:shadowColor.
        self displayForm:shadowForm x:hx y:hy.
    ].
    lightForm notNil ifTrue:[
        self paint:lightColor.
        self displayForm:lightForm x:hx y:hy.
    ].
    self paint:viewBackground

    "Modified: 7.11.1996 / 20:25:33 / cg"
!

invertHandleBarAtX:hx y:hy
    trackLine == #dashedLine ifTrue:[
        self lineStyle:#dashed.
    ].

    self clippedByChildren:false.

    self xoring:[
        |yL xL halfHeight|

        halfHeight := barHeight // 2.
        yL := hy + halfHeight - 1.
        xL := hx + halfHeight - 1.

        orientation == #vertical ifTrue:[
            (trackLine == #solidLine 
            or:[trackLine == #dashedLine]) ifTrue:[
                self displayLineFromX:0 y:yL toX:width y:yL.
            ] ifFalse:[
                self fillRectangleX:0 y:hy width:width height:barHeight
            ]
        ] ifFalse:[
            (trackLine == #solidLine 
            or:[trackLine == #dashedLine]) ifTrue:[
                self displayLineFromX:xL y:0 toX:xL y:height.
            ] ifFalse:[
                self fillRectangleX:hx y:0 width:barHeight height:height
            ]
        ].
    ].
    self clippedByChildren:true.
    trackLine == #dashedLine ifTrue:[
        self lineStyle:#solid.
    ].

    "Modified: 19.3.1997 / 11:18:54 / cg"
    "Modified: 28.4.1997 / 14:56:26 / dq"
!

lockRedraw
    redrawLocked := true
!

redraw
    "redraw all of the handles"

    redrawLocked ~~ true ifTrue:[
        self redrawHandlesFrom:1 to:(self subViews size)
    ]

    "Modified: 28.1.1997 / 17:54:15 / cg"
!

redrawHandlesFrom:start to:stop
    "redraw some handles"

    (self subViews size > 0) ifTrue:[
        showHandle ifTrue:[
            self handleOriginsWithIndexFrom:start to:stop do:[:hPoint :hIndex |
                self drawHandle:hIndex atX:(hPoint x) y:(hPoint y)
            ].
        ]
    ]

    "Modified: 28.1.1997 / 17:54:33 / cg"
!

unlockRedraw
    redrawLocked := false
! !

!VariablePanel methodsFor:'enumerating subviews'!

changeSequenceOrderFor:aSubView to:anIndex
    "change a subview's position in the subviews collection.
    "
    |success|

    success := super changeSequenceOrderFor:aSubView to:anIndex.
    success ifTrue:[
        self setupSubviews.
        self resizeSubviews.
    ].
    ^ success
! !

!VariablePanel methodsFor:'event handling'!

sizeChanged:how
    "my size has changed; resize my subviews"

    shown ifTrue:[
        (how == #smaller) ifTrue:[
            self resizeSubviews
        ] ifFalse:[
            "/
            "/ do it in reverse order, to avoid some redraws
            "/
            self resizeSubviewsFrom:(self subViews size) to:1
        ]
    ].
    self changed:#sizeOfView with:how.

    "Modified: 28.1.1997 / 17:56:30 / cg"
! !

!VariablePanel methodsFor:'initializing'!

computeBarHeight
    "compute the height if the separating bar from either the
     form or an explicit height given in the styleSheet"

    <resource: #style (#'variablePanel.barHeight'
                       #'variablePanel.barHeightMM')>

    |bH h|

    shadowForm notNil ifTrue:[
        bH := shadowForm height + 2.
    ] ifFalse:[
        bH := styleSheet at:'variablePanel.barHeight'.
        bH isNil ifTrue:[
            h := styleSheet at:'variablePanel.barHeightMM' default:2.
            bH := (h * device verticalPixelPerMillimeter) rounded.
        ].
    ].
    self barHeight:bH.
    knobHeight := bH.

    handleLabels notNil ifTrue:[
        font := font on:device.
        bH := handleLabels inject:bH into:[:maxSoFar :thisLabel |
                                           thisLabel isNil ifTrue:[
                                                maxSoFar
                                           ] ifFalse:[
                                                maxSoFar max:(thisLabel heightOn:self)
                                           ]
                                          ].
        bH := bH + font descent - 1
    ].

    self barHeight:bH.

    "Modified: / 31.10.1997 / 22:23:44 / cg"
!

defaultControllerClass
    ^ VariablePanelController
!

fixSize 
    super fixSize.
    extentChanged ifTrue:[
        self resizeSubviews
    ].

    "Modified: 22.3.1997 / 01:19:55 / stefan"
!

initCursor
    "set the cursor - a double arrow"

    cursor := self class cursorForOrientation:orientation

    "Modified: 28.3.1997 / 14:45:44 / cg"
!

initStyle
    "setup viewStyle specifics"

    |mm|

    super initStyle.

    handleColor := DefaultHandleColor on:device.

    DefaultHandleStyle isNil ifTrue:[
        handleStyle := styleSheet name
    ] ifFalse:[
        handleStyle := DefaultHandleStyle
    ].

    handleLevel := DefaultHandleLevel.
    showHandle := DefaultShowHandle.
    handlePosition := DefaultHandlePosition.
    trackLine := DefaultTrackingLine.
    separatingLine := DefaultSeparatingLine.

    DefaultHandleImage notNil ifTrue:[
        shadowForm := DefaultHandleImage onDevice:device.
        barWidth := shadowForm width.
    ] ifFalse:[
        handleStyle == #next ifTrue:[
            DefaultHandleImage notNil ifTrue:[
                shadowForm := DefaultHandleImage onDevice:device.
            ] ifFalse:[
                shadowForm := self class shadowFormOn:device.
                lightForm := self class lightFormOn:device.
            ].
            barWidth := shadowForm width.
        ] ifFalse:[
            shadowForm := lightForm := nil.

            mm := device verticalPixelPerMillimeter.
            barWidth := (1.5 * mm) rounded. "motif style width"
        ].
    ].
    self computeBarHeight.

    handleStyle == #mswindows ifTrue:[
        barWidth := (ArrowButton new direction:#up) width + 1 
    ].

    "Modified: / 19.5.1998 / 16:21:02 / cg"
!

initialize
    orientation isNil ifTrue:[orientation := #vertical].
    super initialize.

    "Modified: 7.3.1996 / 14:08:25 / cg"
! !

!VariablePanel methodsFor:'private'!

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

    self subViews do:[:aComponent |
        aComponent relativeCorner isNil ifTrue:[^ true].
        aComponent relativeOrigin isNil ifTrue:[^ true]
    ].
    ^ false

    "Modified: 28.1.1997 / 17:57:26 / cg"
!

handleLabelAt:hIndex
    handleLabels notNil ifTrue:[
        ^ handleLabels at:hIndex ifAbsent:nil
    ].
    ^ nil
!

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

    self handleOriginsWithIndexFrom:1 to:(self subViews size) do:aBlock

    "Modified: 28.1.1997 / 17:53:44 / cg"
!

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

    |x y hw hh hDelta vDelta subViews
     first "{ Class: SmallInteger }"
     last  "{ Class: SmallInteger }"|

    (subViews := self subViews) notNil ifTrue:[
        shadowForm notNil ifTrue:[
            hw := shadowForm width.
            hh := shadowForm height.
        ] ifFalse:[
            hw := hh := barWidth
        ].

        (handleStyle ~~ #normal and:[handleStyle ~~ #mswindows]) ifTrue:[
            hDelta := barWidth // 2.
            vDelta := barWidth // 2.
        ] ifFalse:[
            hDelta := vDelta := 0
        ].

        (handlePosition == #left) ifTrue:[
            x := hDelta. 
            y := vDelta.

            orientation == #vertical ifTrue:[
                x := x + barWidth
            ] ifFalse:[
                y := y + barWidth
            ].
            margin ~~ 0 ifTrue:[
                x := x + 2
            ].
        ] ifFalse:[
            (handlePosition == #right) ifTrue:[
                x := width - hw - margin - hDelta.
                y := height - hh - margin - vDelta.
            ] ifFalse:[
                x := width - barWidth // 2.
                y := height - barWidth // 2
            ]
        ].
        first := start + 1.
        last := stop.

        first to:last do:[:index |
            |view|

            view := subViews at:index.
            orientation == #vertical ifTrue:[
                y := view top "origin y" - barHeight + 1.
            ] ifFalse:[
                x := view left "origin x" - barHeight + 1.
            ].
            aBlock value:(x @ y) value:index
        ]
    ]

    "Modified: / 1.11.1997 / 11:53:40 / cg"
!

resizeSubviews
    "readjust size of all subviews"

    self resizeSubviewsFrom:1 to:(self subViews size)

    "Modified: 28.1.1997 / 17:54:42 / cg"
    "Modified: 22.3.1997 / 01:01:31 / stefan"
!

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

    |step nSubviews subViews|

    (subViews := self subViews) size > 0 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 newExt|

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

            newOrg := view computeOrigin.
            newOrg notNil ifTrue:[
                (index ~~ 1) ifTrue:[
                    orientation == #vertical ifTrue:[
                        newOrg y:(newOrg y + o1)
                    ] ifFalse:[
                        newOrg x:(newOrg x + o1)
                    ]
                ].
            ].
            newExt := view computeExtent.
            newExt notNil ifTrue:[
                orientation == #vertical ifTrue:[
                    newExt y:(newExt y - o2 - o1)
                ] ifFalse:[
                    newExt x:(newExt x - o2 - o1)
                ]
            ].
            view pixelOrigin:newOrg extent:newExt.
        ].
        "/ must clear, since handles are copied automatically (by bitGravity)
        self clear.
        self invalidate.
    ]

    "Modified: 28.1.1997 / 17:55:03 / cg"
    "Modified: 22.3.1997 / 01:02:21 / stefan"
!

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

    |pos delta subViews nSubViews "{ Class: SmallInteger }"|

    "/ setup all subviews to spread evenly ...

    subViews := self subViews.
    nSubViews := subViews size.
    nSubViews == 0 ifTrue:[^ self].

    pos := 0.0. 
    delta := 1.0 / nSubViews.

    1 to:nSubViews do:[:index |
        |view|

        view := subViews at:index.
        orientation == #vertical ifTrue:[
            index == subViews size ifTrue:[
                view origin:(0.0 @ pos) corner:(1.0 @ 1.0)
            ] ifFalse:[
                view origin:(0.0 @ pos) corner:(1.0 @ (pos + delta))
            ].
        ] ifFalse:[
            index == subViews size ifTrue:[
                view origin:(pos @ 0.0) corner:(1.0 @ 1.0)
            ] ifFalse:[
                view origin:(pos @ 0.0) corner:((pos + delta) @ 1.0)
            ].
        ].
        pos := pos + delta
    ]

    "Modified: 28.1.1997 / 17:56:20 / cg"
! !

!VariablePanel methodsFor:'private tableView protocol'!

setupSubviewOrigins
    "setup subviews origins 
     if we only have relative extents 
     (Variable Panels need relative origins and corners!!) (SV 16.1.95)"

    |x y e eX eY subViews n "{ Class: SmallInteger }"|

    x := y := 0.0.

    subViews := self subViews.
    n := subViews size.
    1 to:n do:[:index |
        |view|

        view := subViews at:index.
        e := view relativeExtent.
        e notNil ifTrue:[
            view relativeExtent:nil.
            eX := e x.
            eY := e y.
            index == n ifTrue:[
                view origin:(x @ y) corner:(1.0 @ 1.0)
            ] ifFalse:[
                orientation == #vertical ifTrue:[
                    view origin:(x @ y) corner:(1.0 @ (y+eY))
                ] ifFalse:[
                    view origin:(x @ y) corner:((x+eX) @ 1.0)
                ].
            ].
            orientation == #vertical ifTrue:[
                y := y + eY.
            ] ifFalse:[    
                x := x + eX.
            ]
        ] ifFalse: [
            view origin:(x @ y).
            orientation == #vertical ifTrue:[
                y := view relativeCorner y.
            ] ifFalse:[
                x := view relativeCorner x.
            ]
        ].
    ]

    "Modified: 21.8.1996 / 10:01:29 / stefan"
    "Modified: 28.1.1997 / 17:55:21 / cg"
! !

!VariablePanel class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg/VariablePanel.st,v 1.40 1998-06-04 16:41:02 cg Exp $'
! !