VariablePanel.st
author Claus Gittinger <cg@exept.de>
Tue, 19 Sep 2000 21:03:25 +0200
changeset 2274 df58b2812cde
parent 2270 330980a9e210
child 2279 bd0a6532bf8d
permissions -rw-r--r--
checkin from browser

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

"{ Package: 'stx:libwidg' }"

SimpleView subclass:#VariablePanel
	instanceVariableNames:'barHeight barWidth separatingLine shadowForm lightForm showHandle
		handlePosition handleColor handleStyle handleLevel noColor
		trackLine redrawLocked orientation handleLabels knobHeight
		realRelativeSizes snapAdornment'
	classVariableNames:'DefaultShowHandle DefaultHandleStyle DefaultHandlePosition
		DefaultTrackingLine DefaultSeparatingLine DefaultHandleColor
		DefaultHandleLevel DefaultVCursor DefaultHCursor
		DefaultHandleImage DefaultSnapIcons DefaultSnapHandlePosition'
	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]

   example with snapMode:
                                                                        [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 snapMode:#min.

        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]

"
! !

!VariablePanel class methodsFor:'defaults'!

cursorForOrientation:orientation
    "return an appropriate cursor"

    ^ self cursorForOrientation:orientation onDevice:Display.

    "Modified: / 30.9.1998 / 18:21:10 / cg"
!

cursorForOrientation:orientation onDevice:device
    "return an appropriate cursor"

    |cursor|

    orientation == #vertical ifTrue:[
        DefaultVCursor notNil ifTrue:[
            cursor := DefaultVCursor
        ] ifFalse:[
            device platformName = 'WIN32' ifFalse:[
                cursor := Cursor 
                            sourceForm:(Smalltalk imageFromFileNamed:'VVPanel.xbm' forClass:self)
                            maskForm:(Smalltalk imageFromFileNamed:'VVPanel_m.xbm' forClass:self)
                            hotX:8
                            hotY:8.
            ].

            "
             if bitmaps are not available or under Win95, 
             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:[
            device platformName = 'WIN32' ifFalse:[
                cursor := Cursor 
                            sourceForm:(Smalltalk imageFromFileNamed:'VHPanel.xbm' forClass:self)
                            maskForm:(Smalltalk imageFromFileNamed:'VHPanel_m.xbm' forClass:self)
                            hotX:8
                            hotY:8.
            ].
            "
             if bitmaps are not available or under Win95, 
             use a standard cursor
            "
            cursor isNil ifTrue:[
                "which one looks better ?"
                cursor := Cursor leftRightArrow
                "cursor := Cursor leftLimitArrow"
            ].
            DefaultHCursor := cursor
        ]
    ].

    ^ cursor

    "
     DefaultVCursor := DefaultHCursor := nil.
    "

    "Created: / 30.9.1998 / 18:20:41 / cg"
    "Modified: / 30.9.1998 / 18:23:07 / cg"
!

lightFormOn:aDisplay
    "use same handle as Scroller"

    ^ Scroller handleLightFormOn:aDisplay
!

shadowFormOn:aDisplay
    "use same handle as Scroller"

    ^ Scroller handleShadowFormOn:aDisplay
!

snapIcons
    "returns dictionary of snapIcons
    "
    |upIcon snapIcons|

    DefaultSnapIcons isNil ifTrue:[
        DefaultSnapIcons := IdentityDictionary new.

        DefaultSnapIcons at:#iconUp    put:self snapIconUp.
        DefaultSnapIcons at:#iconRight put:self snapIconRight.
        DefaultSnapIcons at:#iconDown  put:self snapIconDown.
        DefaultSnapIcons at:#iconLeft  put:self snapIconLeft.

        DefaultSnapIcons at:#iconUpDown    put:self snapIconUpDown.
        DefaultSnapIcons at:#iconLeftRight put:self snapIconLeftRight.
    ].
    ^ DefaultSnapIcons
"
DefaultSnapIcons := nil.
self snapIcons
"
!

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.snapHandlePosition' 
                       #'variablePanel.trackingLine'   
                       #'variablePanel.trackingStyle'
                       #'variablePanel.separatingLine' 
                       #'variablePanel.handleColor')>

    |lineModeBoolean|

    DefaultVCursor := DefaultHCursor := nil.

    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.
    ].
    DefaultSnapHandlePosition := StyleSheet at:#'variablePanel.snapHandlePosition' default:DefaultHandlePosition.
    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: / 13.12.1999 / 12:08:33 / cg"
! !

!VariablePanel class methodsFor:'image specs'!

snapIconDown
    "This resource specification was automatically generated
     by the ImageEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the ImageEditor may not be able to read the specification."

    "
     self snapIconDown inspect
     ImageEditor openOnClass:self andSelector:#snapIconDown
    "

    <resource: #image>

    ^Icon
        constantNamed:#'VariablePanel snapIconDown'
        ifAbsentPut:[(Depth4Image new) width: 62; height: 5; photometric:(#palette); bitsPerSample:(#(4 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@L3@CL0@3LAL3@SL0D3LAL3@SL0D3L@@@@@@@@@@@@C@P@0D@LA@S@PD0DALA@S@PD0DALA@@
@@@@@@@@@@@QD@DQ@ADP@QD@DQ@ADP@QD@DQ@ADP@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@b') ; colorMapFromArray:#[0 0 0 68 68 68 141 141 141 255 255 255]; mask:((Depth1Image new) width: 62; height: 5; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@A?LX1#FLX3>C8)R%JT)R''0GA#FLX1#FN@H@@@@@@@@P@@a') ; yourself); yourself]!

snapIconLeft
    "This resource specification was automatically generated
     by the ImageEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the ImageEditor may not be able to read the specification."

    "
     self snapIconLeft inspect
     ImageEditor openOnClass:self andSelector:#snapIconLeft
    "

    <resource: #image>

    ^Icon
        constantNamed:#'VariablePanel snapIconLeft'
        ifAbsentPut:[(Depth4Image new) width: 5; height: 62; photometric:(#palette); bitsPerSample:(#(4 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@3D@@0D@@1D@@@@@@@@@@3D@@0D@@1D@@@@@@@@@@3D@@0D@@1D@@@@@@AD@@3D@@0D@@1D@@@@@@AD@
@3D@@0D@@1D@@@@@@AD@@3D@@0D@@1D@@@@@@AD@@3D@@0D@@1D@@@@@@AD@@3D@@0D@@1D@@@@@@AD@@3@@@0D@@AD@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@') ; colorMapFromArray:#[0 0 0 68 68 68 141 141 141 255 255 255]; mask:((Depth1Image new) width: 5; height: 62; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@A@0\OA0LA@D@6UPL@@@XE@0@@A TC@@@FAPL@@@XE@0@@A UCLD@FAPL@@@XE@0@@A TC@@DCA0=''T0D@@b') ; yourself); yourself]!

snapIconLeftRight
    "This resource specification was automatically generated
     by the ImageEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the ImageEditor may not be able to read the specification."

    "
     self snapIconLeftRight inspect
     ImageEditor openOnClass:self andSelector:#snapIconLeftRight
    "

    <resource: #image>

    ^Icon
        constantNamed:#'VariablePanel snapIconLeftRight'
        ifAbsentPut:[(Depth4Image new) width: 5; height: 62; photometric:(#palette); bitsPerSample:(#(4 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@3@@@0D@@AD@@@@@@@@@@3L@@0D@@QD@@@@@@@@@L3L3@@@@@@@@@@@@@@@@@3L@@0D@@QD@@@@@@@@@
@3L@@0D@@QD@@@@@@@@@@3L@@0D@@QD@@@@@@@@@L3L0@@@C@@@@@@@@@@@@@3L@@0D@@QD@@@@@@@@@@3L@@0D@@QD@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@') ; colorMapFromArray:#[0 0 0 68 68 68 141 141 141 255 255 255]; mask:((Depth1Image new) width: 5; height: 62; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:' LC <NK@ @@A@&QPLP@@XE@0@@C<A? A@VAPL@@@XE@0@@A TCL@@O @>@@BXE@0@PY$TCD@@A@0\OA0LAXb') ; yourself); yourself]!

snapIconRight
    "This resource specification was automatically generated
     by the ImageEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the ImageEditor may not be able to read the specification."

    "
     self snapIconRight inspect
     ImageEditor openOnClass:self andSelector:#snapIconRight
    "

    <resource: #image>

    ^Icon
        constantNamed:#'VariablePanel snapIconRight'
        ifAbsentPut:[(Depth4Image new) width: 5; height: 62; photometric:(#palette); bitsPerSample:(#(4 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@3@@@0D@@AD@@Q@@@@@@@3L@@0D@@QD@@Q@@@@@@@3L@@0D@@QD@@Q@@@@@@@3L@@0D@@QD@@Q@@@@@@@3L@
@0D@@QD@@Q@@@@@@@3L@@0D@@QD@@Q@@@@@@@3L@@0D@@QD@@@@@@@@@@3L@@0D@@QD@@@@@@@@@@3L@@0D@@QD@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
@@@@@@@@') ; colorMapFromArray:#[0 0 0 68 68 68 141 141 141 255 255 255]; mask:((Depth1Image new) width: 5; height: 62; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@4A \G%2X4@AXE@0@@A TC@E@6AQL@@@XE@0@@A TC@@@6APL@@@XEL0@@A UC\@@VAPL@@@PFA0^''M PP@b') ; yourself); yourself]!

snapIconUp
    "This resource specification was automatically generated
     by the ImageEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the ImageEditor may not be able to read the specification."

    "
     self snapIconUp inspect
     ImageEditor openOnClass:self andSelector:#snapIconUp
    "

    <resource: #image>

    ^Icon
        constantNamed:#'VariablePanel snapIconUp'
        ifAbsentPut:[(Depth4Image new) width: 62; height: 5; photometric:(#palette); bitsPerSample:(#(4 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@CL0@3L@L3@CL0@3L@L3@CL0@3@@L0@@@@@@@@@@@@@0DPLADC@Q@0DPLADC@Q@0D@LA@C@P@@
@@@@@@@@@@@QD@DQ@ADP@QD@DQ@ADP@Q@@DP@AD@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@b') ; colorMapFromArray:#[0 0 0 68 68 68 141 141 141 255 255 255]; mask:((Depth1Image new) width: 62; height: 5; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'B@@@@@@@@D@\X1#FLX1 8C9R%JT)R%G0_3FLX1#FL? @@@@@@@@@@@@a') ; yourself); yourself]!

snapIconUpDown
    "This resource specification was automatically generated
     by the ImageEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the ImageEditor may not be able to read the specification."

    "
     self snapIconUpDown inspect
     ImageEditor openOnClass:self andSelector:#snapIconUpDown
    "

    <resource: #image>

    ^Icon
        constantNamed:#'VariablePanel snapIconUpDown'
        ifAbsentPut:[(Depth4Image new) width: 62; height: 5; photometric:(#palette); bitsPerSample:(#(4 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
@@@@@@@@@@@@@@@0@@@@@@@@@@@@L@@@@@@@@@@@@@@@@@@@L0@CL@@@L@L0@CL@@3@@@C@CL@@3@@@@@@@@@@@@@C@P@0D@DC@C@P@0D@LA@@@0@0D@LA@@
@@@@@@@@@@@AD@@Q@@@0@AD@@Q@@DP@@L@@Q@@DP@@@@@@@@@@@@@@@@@@@@L@@@@@@@@@@@@C@@@@@@@@@@@@@b') ; colorMapFromArray:#[0 0 0 68 68 68 141 141 141 255 255 255]; mask:((Depth1Image new) width: 62; height: 5; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@J@@B @@@PLX)#FJX1?C )R%JT)R#8_A#JLX2#FGC>@@(@@J@@H@@a') ; yourself); yourself]! !

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

    |bH|

    bH := nPixel.

    "make certain bar is visible and catchable"
    (bH < 4) ifTrue:[
        bH := 4
    ].

    "make it even, so spacing is equally spreadable among subviews"
    bH odd ifTrue:[
        bH := bH + 1
    ].
    self setBarHeight:bH

    "Modified: / 28.4.1997 / 14:30:33 / dq"
    "Modified: / 30.1.2000 / 22:31:32 / cg"
!

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
    "define special handle labels - typically a collection of
     bitmap images. Notice, that the first handle is not
     drawn, that is, the first element if the argument is useless."

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

    handleLabels := aCollectionOfLabels.
    self computeBarHeight.
    self resizeSubviews.

    "
     |top panel v1 v2|

     top := StandardSystemView new.
     panel := VariableVerticalPanel origin:0.0@0.0 corner:1.0@1.0 in:top.
     panel add:(EditTextView origin:0.0@0.0 corner:1.0@0.5).
     panel add:(EditTextView origin:0.0@0.5 corner:1.0@1.0).
     panel handleStyle:nil.
     panel handleLabels:#('foo' 'bar').
     top open
    "
!

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 ifTrue:[
        handleLevel := aNumber.
        shown ifTrue:[
            self clear.
            self invalidate
        ]
    ]
!

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.
     If never set by the program, the position is controlled by the styleSheet."

    handlePosition ~~ aSymbol ifTrue:[
        handlePosition := aSymbol ? DefaultHandlePosition.
        shown ifTrue:[
            self clear.    
            self invalidate
        ]
    ]
!

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 clear.
            self invalidate
        ]
    ]

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

setBarHeight:nPixel
    "check whether snap matches to extent of bar otherwise disable snap
    "
    snapAdornment notNil ifTrue:[
        barHeight := nPixel max:(snapAdornment at:#height ifAbsent:0)
    ] ifFalse:[
        barHeight := nPixel max:0
    ].

    realized ifTrue:[
        self resizeSubviews
    ]

!

showHandle
    "return the the handle-drawing flag; aBoolean"

    ^ showHandle
!

showHandle:aBoolean
    "enabled/disable the handle-drawing"

    showHandle ~~ aBoolean ifTrue:[
        showHandle := aBoolean ? DefaultShowHandle.
        realized ifTrue:[
            self clear.
            self invalidate
        ]
    ]
!

snapHandlePosition
    "return the position of the snap-handle"

    ^ self handlePosition. "/ ^ snapHandlePosition
!

snapHandlePosition:aSymbol
    "define the position of the snap-handle; the argument aSymbol
     may be one of #left, #right or #center.
     If never set by the program, the position is controlled by the styleSheet."

    self handlePosition:aSymbol.

"/    snapHandlePosition := aSymbol.
"/    realized ifTrue:[
"/        self invalidate
"/    ]
!

snapMode
    "allowed modes are:
        nil             no snap

        #max            on press the view is increased to bottom(vertical) or right(horizontal)
        #min            on press the view is decreased to top   (vertical) or left (horizontal)
        #maxMin         on press the view is increased or decreased dependent on its current extent
        #minMax         on press the view is increased or decreased dependent on its current extent
    "
    snapAdornment notNil ifTrue:[
        ^ snapAdornment at:#mode ifAbsent:nil
    ].
    ^ nil

!

snapMode:aMode
    "allowed modes are:
        nil             no snap

        #max            on press the view is increased to bottom(vertical) or right(horizontal)
        #min            on press the view is decreased to top   (vertical) or left (horizontal)
        #maxMin         on press the view is increased or decreased dependent on its current extent
        #minMax         on press the view is increased or decreased dependent on its current extent
    "
    |oldHeight oldMode|

    aMode notNil ifTrue:[
        ( #( max min maxMin minMax both) includes:aMode) ifFalse:[
            ^ self error:('unknown snapMode: ', aMode printString).
        ]
    ].
    (oldMode := self snapMode) == aMode ifTrue:[^ self].

    (snapAdornment notNil and:[aMode notNil]) ifTrue:[
        "must only redraw"
        snapAdornment at:#mode put:aMode
    ] ifFalse:[
        "must recompute barHeight and redraw"

        aMode isNil ifTrue:[
            snapAdornment := nil
        ] ifFalse:[
            self initSnapAdornment.
            snapAdornment at:#mode put:aMode.
        ].
        oldHeight := barHeight.

        self computeBarHeight.

        oldHeight ~~ barHeight ifTrue:[
            "must recompute subViews"
            self setupSubviews.
            self resizeSubviews.
        ]
    ].
    shown ifTrue:[
        self clear.
        self invalidate
    ].
!

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 xm ym lbl maxKnob
     mar           "{ Class: SmallInteger }"
     barWidthInt   "{ Class: SmallInteger }"
     barHeightInt  "{ Class: SmallInteger }" |

    ((handleStyle isNil or:[handleStyle == #none])
    and:[handleLabels isNil]) 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.
        handleStyle == #full ifTrue:[
            w := h := maxKnob
        ] ifFalse:[
            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 isNil
        or:[handleStyle == #none]) ifFalse:[
            (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
                        ].
                        ym := y + m.

                        handleStyle == #full ifTrue:[
                            handleLevel ~~ 0 ifTrue:[
                                self 
                                    drawEdgesForX:0 "/ -(handleLevel abs)
                                    y:ym "/-1
                                    width:width "/+(handleLevel+handleLevel)abs
                                    height:h-2 
                                    level:handleLevel
                                    shadow:shadowColor 
                                    light:lightColor
                                    halfShadow:nil 
                                    halfLight:nil 
                                    style:nil 
                            ]
                        ] ifFalse:[
                            handleLevel ~~ 0 ifTrue:[
                                self drawEdgesForX:(hx - barWidthInt)
                                                 y:ym
                                             width:(barWidthInt + barWidthInt)
                                            height:h 
                                             level:handleLevel.
                            ].

                            handleStyle == #iris ifTrue:[
                                self paint:handleColor.
                                self fillDeviceRectangleX:(hx - barWidthInt + 2)
                                                        y:(ym + 2)
                                                    width:(barWidthInt + barWidthInt - 4)
                                                   height:h - 4
                            ]
                        ]
                    ].
                ] ifFalse:[
                    y := hy.
                    (shadowForm notNil or:[lightForm notNil]) ifTrue:[
                        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 isNil
        or:[handleStyle == #none]) ifFalse:[
            (handleStyle ~~ #normal
            and:[handleStyle ~~ #mswindows]) ifTrue:[
                 m := (barHeightInt - w) // 2.
                m := (maxKnob - 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.
                        ].
                        xm := x + m.
                        handleStyle == #full ifTrue:[
                            handleLevel ~~ 0 ifTrue:[
                                self 
                                    drawEdgesForX:xm "/-1
                                    y:0 "/ -handleLevel
                                    width:w-2
                                    height:height "/ +handleLevel+handleLevel 
                                    level:handleLevel
                                    shadow:shadowColor 
                                    light:lightColor
                                    halfShadow:nil 
                                    halfLight:nil 
                                    style:nil
                            ]
                        ] ifFalse:[
                            handleLevel ~~ 0 ifTrue:[
                                self drawEdgesForX:xm
                                                 y:(hy - barWidthInt)
                                             width:w 
                                            height:(barWidthInt + barWidthInt)
                                             level:handleLevel.
                            ].
                            handleStyle == #iris ifTrue:[
                                self paint:handleColor.
                                self fillDeviceRectangleX:(xm + 2)
                                                        y:(hy - barWidthInt + 2)
                                                    width:w - 4
                                                   height:(barWidthInt + barWidthInt - 4)
                            ].
                        ].
                    ]
                ] ifFalse:[
                    x := hx.
                    (shadowForm notNil or:[lightForm notNil]) ifTrue:[
                        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: / 29.7.1998 / 22:48:33 / 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"
!

drawSnapAt:anIndex
    "draw the snap for a handle at an index
    "
    |layout icon level offLevel paint canChangeExtent
     left   "{ Class:SmallInteger }"
     top    "{ Class:SmallInteger }"
     width  "{ Class:SmallInteger }"
     height "{ Class:SmallInteger }"
     snapMode leftEdge wEdge topEdge hEdge part wPart hPart
    |

    (layout := self snapLayoutAt:anIndex) isNil ifTrue:[
        "snap disabled"
        ^ self
    ].

    left   := layout left.
    top    := layout top.
    width  := layout width.
    height := layout height.
    snapMode := self snapMode.

    offLevel := level := snapAdornment at:#level ifAbsent:0.

    canChangeExtent := self canChangeExtentOfViewAt:anIndex.
    canChangeExtent ifTrue:[
        (controller isSnapEntered:anIndex) ifTrue:[
            controller isSnapPressed ifTrue:[
                level := #selectedLevel.
                paint := #selectedBgColor.
            ] ifFalse:[
                level := #enterLevel.
                paint := #enterBgColor.
            ].
            level := snapAdornment at:level ifAbsent:0.
        ]
    ].
    paint notNil ifTrue:[
        paint := snapAdornment at:paint ifAbsent:viewBackground
    ] ifFalse:[
        paint := viewBackground
    ].
    self paint:paint.

    level == 0 ifTrue:[
    ].

    self fillRectangleX:left+1 y:top+1 width:width-2 height:height-2.

    level ~~ 0 ifTrue:[
        leftEdge := left + 1.
        wEdge := wPart := width - 2.
        topEdge := top + 1.
        hEdge := hPart := height - 2.

        orientation == #vertical ifTrue:[
            wPart := width // 3.
        ] ifFalse:[
            hPart := height // 3.
        ].

        level < 0 ifTrue:[
            part := (self subViews at:anIndex) objectAttributeAt:#snapPart.
            part == #left ifTrue:[
                self drawEdgesForX:leftEdge y:topEdge width:wEdge height:hEdge level:offLevel.
                wPart := wPart + 1.
            ] ifFalse:[
                part == #middle ifTrue:[
                    self drawEdgesForX:leftEdge y:topEdge width:wEdge height:hEdge level:offLevel.
                    orientation == #vertical ifTrue:[
                        leftEdge := leftEdge + wPart.
                    ] ifFalse:[
                        topEdge := topEdge + hPart.
                    ]
                ] ifFalse:[
                    part == #right ifTrue:[
                        self drawEdgesForX:leftEdge y:topEdge width:wEdge height:hEdge level:offLevel.
                        orientation == #vertical ifTrue:[
                            leftEdge := leftEdge + (width - wPart - 1).
                        ] ifFalse:[
                            topEdge := topEdge + (height - hPart - 1).
                        ].
                        wPart := wPart - 1.
                    ]
                ]
            ].
            wEdge := wPart.
            hEdge := hPart.
        ].
        self drawEdgesForX:leftEdge y:topEdge width:wEdge height:hEdge level:level.
    ].

    canChangeExtent ifFalse:[^ self].

    snapMode == #both ifTrue:[
        icon := orientation == #vertical ifTrue:[#iconUpDown] ifFalse:[#iconLeftRight]
    ] ifFalse:[
        (self snapAtIndexWillGrow:anIndex) ifTrue:[
            icon := orientation == #vertical ifTrue:[#iconDown] ifFalse:[#iconRight]
        ] ifFalse:[
            icon := orientation == #vertical ifTrue:[#iconUp]   ifFalse:[#iconLeft]
        ].
    ].
    icon := snapAdornment at:icon ifAbsent:nil.

    icon displayOn:self x:(left + (width - icon width // 2))
                        y:(top  + (height - icon height // 2)).
!

invertHandleBarAtX:hx y:hy
    |doLine oldStyle|

    doLine := (trackLine == #solidLine 
               or:[trackLine == #dashedLine
               or:[trackLine == #dottedLine]]).

    trackLine == #dashedLine ifTrue:[
        oldStyle := lineStyle.
        self lineStyle:#dashed.
    ] ifFalse:[
        trackLine == #dottedLine ifTrue:[
            oldStyle := lineStyle.
            self lineStyle:#dotted.
        ]
    ].

    self clippedByChildren:false.

    self xoring:[
        |yL xL halfHeight|

        halfHeight := (barHeight // 2) - 1.

        orientation == #vertical ifTrue:[
            yL := hy + halfHeight.
            doLine ifTrue:[
                self displayLineFromX:0 y:yL toX:width y:yL.
            ] ifFalse:[
                self fillRectangleX:0 y:hy width:width height:barHeight
            ]
        ] ifFalse:[
            xL := hx + halfHeight.
            doLine ifTrue:[
                self displayLineFromX:xL y:0 toX:xL y:height.
            ] ifFalse:[
                self fillRectangleX:hx y:0 width:barHeight height:height
            ]
        ].
    ].
    self clippedByChildren:true.

    oldStyle notNil ifTrue:[
        self lineStyle:oldStyle.
    ].

    "Modified: / 28.4.1997 / 14:56:26 / dq"
    "Modified: / 3.5.1999 / 18:49:04 / cg"
!

lockRedraw
    redrawLocked := true
!

redraw
    "redraw all of the handles"

    redrawLocked ~~ true ifTrue:[
        "/ self clear.
        self redrawHandlesFrom:1 to:(self subViews size)
    ]

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

redrawHandlesFrom:start to:stop
    "redraw some handles and snaps
    "
    subViews size ~~ 0 ifTrue:[
        "/ do not draw handle, if there is a snapper ...
        (showHandle and:[snapAdornment isNil]) ifTrue:[
            self handleOriginsWithIndexFrom:start to:stop do:[:hPoint :hIndex |
                self drawHandle:hIndex atX:(hPoint x) y:(hPoint y).
            ]
        ].

        snapAdornment notNil ifTrue:[
            start to:stop do:[:i| self drawSnapAt:i ].
        ].
    ].
!

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"

    realized 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:'focus handling'!

wantsFocusWithButtonPress
    "no, do not catch the keyboard focus on button click"

    ^ false


! !

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

    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.
        ].
    ].
    lvl := styleSheet at:#'variablePanel.barLevel' default:0.
    lvl ~~ 0 ifTrue:[
        bH := bH + (lvl abs * 2).
    ].

    self barHeight:bH.
    knobHeight := bH.

    handleLabels notNil ifTrue:[
        font := font onDevice: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: / 29.7.1998 / 14:47:21 / 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
                onDevice:device

    "Modified: / 30.9.1998 / 18:20:35 / cg"
!

initStyle
    "setup viewStyle specifics"

    |mm|

    super initStyle.

    handleColor := DefaultHandleColor onDevice:device.

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

    handleLevel := DefaultHandleLevel.
    showHandle := DefaultShowHandle.
    handlePosition := DefaultHandlePosition.
    "/ snapHandlePosition := DefaultSnapHandlePosition.
    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.
    self bitGravity:nil.

    "Modified: / 29.7.1998 / 16:07:23 / 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"
!

expandSubView:expandedView
    "expand one of my subviews to full size"

    |pos subViews|

    realRelativeSizes notNil ifTrue:[
        "/ already expanded ..
        ^ self
    ].

    pos := 0.0. 
    subViews := self subViews.

    orientation == #vertical ifTrue:[
        realRelativeSizes := subViews collect:[:v | v relativeCorner y - v relativeOrigin y].
    ] ifFalse:[
        realRelativeSizes := subViews collect:[:v | v relativeCorner x - v relativeOrigin x].
    ].

    subViews do:[:aSubView |
        aSubView == expandedView ifTrue:[
            aSubView origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).
            pos := 1.0
        ] ifFalse:[
            orientation == #vertical ifTrue:[
                aSubView origin:(0.0 @ pos) corner:(1.0 @ pos)
            ] ifFalse:[
                aSubView origin:(pos @ 0.0) corner:(pos @ 1.0)
            ]
        ]
    ].
    self resizeSubviews.

    "Modified: 28.1.1997 / 17:56:20 / 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"
!

resizeSubViewsTo:relativeSizeList
    "change subviews sizes as defined in the argument list
     (a collection of relative sizes)"

    |pos subViews|

    subViews := self subViews.

    pos := 0.0.
    subViews with:relativeSizeList do:[:aSubView :relSize |
        orientation == #vertical ifTrue:[
            aSubView origin:(0.0 @ pos) corner:(1.0 @ (pos + relSize))
        ] ifFalse:[
            aSubView origin:(pos @ 0.0) corner:((pos + relSize) @ 1.0)
        ].
        pos := pos + relSize.
    ].
    self resizeSubviews.

!

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 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.
        ].
        shown ifTrue:[
            "/ must clear, since handles are copied automatically (by bitGravity)
            self clear.
            self invalidate.
        ]
    ]

    "Modified: / 22.3.1997 / 01:02:21 / stefan"
    "Modified: / 23.2.2000 / 18:32:37 / cg"
!

restoreSubViewRatios
    "restore my subviews sizes to the state before the full-expand"

    |pos subViews |

    realRelativeSizes == nil ifTrue:[
        "/ not expanded - ignore
        ^ self
    ].

    pos := 0.0.
    self subViews with:realRelativeSizes do:[:aSubView :aRelativeSize |
        orientation == #vertical ifTrue:[
            aSubView origin:(0.0 @ pos) corner:(1.0 @ (pos+aRelativeSize))
        ] ifFalse:[
            aSubView origin:(pos @ 0.0) corner:((pos+aRelativeSize) @ 1.0)
        ].
        pos := pos + aRelativeSize
    ].
    realRelativeSizes := nil.
    self resizeSubviews.

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

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 org corn|

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

    "Modified: / 23.2.2000 / 18:14:01 / cg"
! !

!VariablePanel methodsFor:'private snap queries'!

canChangeExtentOfViewAt:anIndex
    "returns true if extent at an index is changable
    "
    |view|

    view := subViews at:anIndex ifAbsent:[^ false].

    orientation == #vertical ifTrue:[
        view height > 2 ifFalse:[
            view := subViews at:(anIndex + 1) ifAbsent:[^ false].
          ^ view height > 2
        ].
        ^ true
    ].

    view width > 2 ifFalse:[
        view := subViews at:(anIndex + 1) ifAbsent:[^ false].
      ^ view width > 2
    ].
    ^ true


!

initSnapAdornment
    |num icon level enterLevel selectedLevel color|

    snapAdornment notNil ifTrue:[^ snapAdornment ].

    snapAdornment := IdentityDictionary new.

    level         := styleSheet at:#'variablePanel.snapLevel'      default:1.
    enterLevel    := styleSheet at:#'variablePanel.snapEnterLevel' default:level.
    selectedLevel := styleSheet at:#'variablePanel.selectedLevel'  default:(level negated).

    snapAdornment at:#level         put:level.
    snapAdornment at:#enterLevel    put:enterLevel.
    snapAdornment at:#selectedLevel put:selectedLevel.
    snapAdornment at:#mode          put:#min.

    color := styleSheet colorAt:#'variablePanel.snapSelectedBgColor'
                                      default:(StyleSheet colorAt:#'button.activeBackgroundColor').
    color notNil ifTrue:[
        snapAdornment at:#selectedBgColor put:(color onDevice:device)
    ].

    color := StyleSheet colorAt:#'variablePanel.snapEnterBgColor'
                        default:(StyleSheet colorAt:#'button.enteredBackgroundColor').
    color notNil ifTrue:[
        snapAdornment at:#enterBgColor put:(color onDevice:device)
    ].

    self class snapIcons keysAndValuesDo:[:aKey :anIcon|
        icon := anIcon copy onDevice:device.
        icon clearMaskedPixels.
        snapAdornment at:aKey put:icon
    ].
    "compute required snap extent including level and margins ..."

    num  := level abs max:(enterLevel abs).
    num  := num max:(selectedLevel abs).
    num  := num + 2 "margin into handle := 1" * 2.
    icon := snapAdornment at:#iconUp.

    snapAdornment at:#height put:(icon height + num).
    snapAdornment at:#width  put:(icon width  + num).

  ^ snapAdornment

!

snapAtIndexWillGrow:anIndex
    "returns true if the view assigned to the snap at an index will grow
     if pressing the snap
    "
    |view mode|

    (mode := self snapMode) notNil ifTrue:[
        (mode == #max or:[mode == #maxMin]) ifTrue:[
            "on press the view is increased to bottom(vertical) or right(horizontal)"
            view := subViews at:(anIndex + 1) ifAbsent:[^ false].
          ^ orientation == #vertical ifTrue:[view height > 2] ifFalse:[view width  > 2]
        ].    

        (mode == #min or:[mode == #minMax]) ifTrue:[
            "on press the view is decreased to top(vertical) or left (horizontal)"
            view := subViews at:anIndex ifAbsent:[^ false].
          ^ orientation == #vertical ifTrue:[view height <= 2] ifFalse:[view width  <= 2]
        ].

        self error:'unexepected snapMode state'.
    ].    
    ^ false     "snap is diasbled"
!

snapLayoutAt:anIndex
    "returns the layout of the snap at an index
     or nil if snaps are disabled
    "
    |v1 v2 left top w snapX snapY|

    snapAdornment isNil ifTrue:[^ nil].         "snap disabled"

    v1 := subViews at:anIndex     ifAbsent:[^ nil].
    v2 := subViews at:anIndex + 1 ifAbsent:[^ nil].
    w  := snapAdornment at:#width ifAbsent:0.

    handlePosition "snapHandlePosition" == #left ifTrue:[
        snapX := snapY := margin. "/ ViewSpacing.
    ] ifFalse:[
        handlePosition "snapHandlePosition" == #right ifTrue:[
            snapX := width - w.
            snapY := height - w.
        ] ifFalse:[
            snapX := (width - w) // 2.
            snapY := (height - w) // 2.
        ].
    ].

    orientation == #vertical ifTrue:[
        left := snapX. "/ v1 width - w // 2.
      ^ Rectangle left:left top:(v1 bottom + 1) right:(left + w) bottom:(v2 top)
    ].

    top := snapY. "/ v1 height - w // 2.
  ^ Rectangle left:(v1 right + 1) top:top right:(v2 left) bottom:(top + w)
! !

!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.71 2000-09-19 19:03:25 cg Exp $'
! !