VarPanel.st
author Claus Gittinger <cg@exept.de>
Wed, 29 May 1996 16:40:41 +0200
changeset 722 3f297a438fec
parent 593 86dd024ed773
child 826 138bc07c873b
permissions -rw-r--r--
use #invalidate instead of #redraw

"
 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'
	classVariableNames:'DefaultShowHandle DefaultHandleStyle DefaultHandlePosition
		DefaultTrackingLine DefaultSeparatingLine DefaultHandleColor
		DefaultHandleLevel DefaultVCursor DefaultHCursor'
	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:]
        variablePanelShowHandle         true/false - should a handle be shown (default:true)

        variablePanelHandleStyle        #next / #motif / nil (special handles)

        variablePanelHandlePosition     #left / #center / #right (default:#right)

        variablePanelHandleLevel        3D level of heandle (default:2)

        variablePanelTrackingLine       when moved, track an inverted line (as in motif)
                                        as opposed to tracking the whole bar (default:false)

        variablePanelSeparatingLine     draw a separating line in the bar as in motif (default:false)

        variablePanelHandleColor        color of the handle. (default:Black)

        variablePanelHandleEnteredColor color of the handle when the pointer is in the bar (default:nil)

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

examples
"
   example (setting the orientation later makes it equally space its views):
                                                                        [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.

        v1 := View in:p.
        v2 := View in:p.
        v3 := View in:p.

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

        p orientation:#vertical.
        top open.
                                                                        [exEnd]


   example (setting orientation first, req's that subviews 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]



   example (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]



   example (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]



    example (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]


    example: (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]


    example: (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]


   example (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.

        f1 := View in:p.
        f2 := View in:p.
        f3 := View 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).

        p orientation:#vertical.
        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'!

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 (#variablePanelShowHandle #variablePanelHandleStyle
                       #variablePanelHandlePosition #variablePanelHandleLevel
                       #variablePanelTrackingLine 
                       #variablePanelSeparatingLine #variablePanelHandleColor)>

    DefaultShowHandle := StyleSheet at:'variablePanelShowHandle' default:true.
    DefaultHandleStyle := StyleSheet at:'variablePanelHandleStyle'.
    DefaultHandlePosition := StyleSheet at:'variablePanelHandlePosition' default:#right.
    DefaultHandleLevel := StyleSheet at:'variablePanelHandleLevel' default:2.
    DefaultTrackingLine := StyleSheet at:'variablePanelTrackingLine' default:false.
    DefaultSeparatingLine := StyleSheet at:'variablePanelSeparatingLine' default:false.
    DefaultHandleColor := StyleSheet colorAt:'variablePanelHandleColor' default:Black.

    "Modified: 1.3.1996 / 13:51:24 / cg"
! !

!VariablePanel methodsFor:'accessing'!

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

    super addSubView:aView.
    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
	]
    ]
! !

!VariablePanel methodsFor:'accessing-look'!

barHeight
    "return the height of the separating bar"

    ^ barHeight
!

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

    barHeight := nPixel.

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

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

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
!

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

drawHandleAtX:hx y:hy
    "draw a single handle at hx/hy"

    |h w x y m|

    handleStyle isNil ifTrue:[^ self].

    shadowForm notNil ifTrue:[
	h := shadowForm height.
	w := shadowForm width .
    ] ifFalse:[
	h := w := barHeight - 4.
    ].

    self paint:viewBackground.
    orientation == #vertical ifTrue:[
	self fillRectangleX:margin y:hy 
		      width:(width - margin - margin) 
		     height:barHeight.

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

	    shadowForm isNil ifTrue:[
		y := hy + (barHeight // 2).

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

		handleStyle == #line ifTrue:[
		    self paint:handleColor.
		    self displayLineFromX:hx - barWidth y:y toX:hx + barWidth y:y
		] ifFalse:[
		    y := hy.   
		    handleStyle == #st80 ifTrue:[
			y := y - 1
		    ].
		    self drawEdgesForX:(hx - barWidth)
				     y:(y + m)
				 width:(barWidth + barWidth)
				height:h 
				 level:handleLevel.

		    handleStyle == #iris ifTrue:[
			self paint:handleColor.
			self fillDeviceRectangleX:(hx - barWidth + 2)
						y:(y + m + 2)
					    width:(barWidth + barWidth - 4)
					   height:h - 4
		    ]
		].
	    ] ifFalse:[
		y := hy.
		self drawHandleFormAtX:hx y:(y + m)
	    ].
	    handleStyle == #st80 ifTrue:[
		y := hy - 1.
		self paint:lightColor.
		self displayLineFromX:margin y:y toX:(width - margin - margin - 1) y:y.
		self displayLineFromX:0 y:hy toX:0 y:(hy + barHeight - 1).
		y := hy + barHeight - 2.
		self paint:shadowColor.
		self displayLineFromX:margin y:y toX:(width - margin) 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 + barHeight - 1).
	    ].
	] ifFalse:[
	    y := hy + barHeight - 1.
	    self paint:handleColor.
	    separatingLine ifTrue:[
		self displayLineFromX:0 y:hy+1 toX:width y:hy+1.
		self displayLineFromX:0 y:y toX:width y:y.
	    ].
	    self fillRectangleX:hx y:hy width:barWidth height:barHeight
	]
    ] ifFalse:[
	self fillRectangleX:hx y:margin 
		      width:barHeight
		     height:(height - margin - margin).
	(handleStyle ~~ #normal and:[handleStyle ~~ #mswindows]) ifTrue:[
	     m := (barHeight - w) // 2.
	     shadowForm isNil ifTrue:[
		x := hx + (barHeight // 2).
		separatingLine ifTrue:[
		    self paint:shadowColor.
		    self displayLineFromX:x y:margin toX:x y:(height - margin).
		    x := x + 1.
		    self paint:lightColor.
		    self displayLineFromX:x y:margin toX:x y:(height - margin).
		].
		self paint:viewBackground.
		self fillRectangleX:hx y:(hy - barWidth) 
			      width:w 
			     height:(barWidth + barWidth).

		handleStyle == #line ifTrue:[
		    self paint:handleColor.
		    self displayLineFromX:x y:hy - barWidth toX:x y:hy + barWidth.
		] ifFalse:[
		    x := hx.
		    handleStyle == #st80 ifTrue:[
			x := x - 1.
		    ].
		    self drawEdgesForX:(x + m)
				     y:(hy - barWidth)
				 width:w 
				height:(barWidth + barWidth)
				 level:handleLevel.
		    handleStyle == #iris ifTrue:[
			self paint:handleColor.
			self fillDeviceRectangleX:(x + m + 2)
						y:(hy - barWidth + 2)
					    width:w - 4
					   height:(barWidth + barWidth - 4)
		    ].
		]
	    ] ifFalse:[
		x := hx.
		self drawHandleFormAtX:(x + m) y:hy
	    ].
	    handleStyle == #st80 ifTrue:[
		x := hx - 1.
		self paint:lightColor.
		self displayLineFromX:x y:margin toX:x y:(height - margin).
		self displayLineFromX:hx y:0 toX:(hx + barHeight - 1) y:0.
		x := hx + barHeight - 2.
		self paint:shadowColor.
		self displayLineFromX:x y:margin toX:x y:(height - margin).
		    "uncomment the -1 if you dont like the notch at the bottom end"
		    "                   VVV"
		self displayLineFromX:hx" "-1" " y:height-1 toX:(hx + barHeight - 1) y:height-1.
	    ].
	] ifFalse:[
	    x := hx + barHeight - 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:barHeight height:barWidth
	]
    ].

    "Modified: 24.2.1996 / 19:05:52 / cg"
!

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

    self paint:shadowColor.
    self displayForm:shadowForm x:hx y:hy.
    self paint:lightColor.
    self displayForm:lightForm x:hx y:hy.
    self paint:viewBackground
!

invertHandleBarAtX:hx y:hy
    self noClipByChildren.
    self xoring:[
	|y x|

	orientation == #vertical ifTrue:[
	    trackLine ifTrue:[
		y := hy + (barHeight // 2).
		self displayLineFromX:0 y:y toX:width y:y.
	    ] ifFalse:[
		self fillRectangleX:0 y:hy width:width height:barHeight
	    ]
	] ifFalse:[
	    trackLine ifTrue:[
		x := hx + (barHeight // 2).
		self displayLineFromX:x y:0 toX:x y:height.
	    ] ifFalse:[
		self fillRectangleX:hx y:0 width:barHeight height:height
	    ]
	]
    ].
    self clipByChildren.
!

lockRedraw
    redrawLocked := true
!

redraw
    "redraw all of the handles"

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

redrawHandlesFrom:start to:stop
    "redraw some handles"

    subViews notNil ifTrue:[
	showHandle ifTrue:[
	    self handleOriginsFrom:start to:stop do:[:hPoint |
		self drawHandleAtX:(hPoint x) y:(hPoint y)
	    ].
	]
    ]
!

unlockRedraw
    redrawLocked := false
! !

!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:(subViews size) to:1
	]
    ].
    self changed:#sizeOfView with:how.
! !

!VariablePanel methodsFor:'initializing'!

defaultControllerClass
    ^ VariablePanelController
!

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

initCursor
    "set the cursor - a double arrow"

    orientation == #vertical ifTrue:[
	DefaultVCursor notNil ifTrue:[
	    cursor := DefaultVCursor
	] ifFalse:[
	    cursor := Cursor sourceForm:(Form fromFile:'VVPanel.xbm')
			     maskForm:(Form fromFile:'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:(Form fromFile:'VHPanel.xbm')
			     maskForm:(Form fromFile:'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
	]
    ]
!

initStyle
    |mm h bH|

    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.

    handleStyle == #next ifTrue:[
        shadowForm := self class shadowFormOn:device.
        lightForm := self class lightFormOn:device.

        bH := shadowForm height + 2.
        barWidth := shadowForm width.
    ] ifFalse:[
        shadowForm := lightForm := nil.

        mm := device verticalPixelPerMillimeter.
        self is3D ifTrue:[
            h := 3
        ] ifFalse:[
            h := 2
        ].
        bH := (h * mm) rounded.
        barWidth := (2 * mm) rounded. "motif style width"
    ].
    self barHeight:bH.

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

    "Modified: 8.3.1996 / 11:51:59 / 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"

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

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

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

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

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

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

    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
	] 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)
	]
    ]
!

resizeSubviews
    "readjust size of some subviews"

    self resizeSubviewsFrom:1 to:(subViews size)
!

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

    |step nSubviews|

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

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

	    relOrg := view relativeOrigin.
	    relOrg isNil ifTrue:[
		self error:'subview must have relative origin'
	    ].
	    newOrg := view originFromRelativeOrigin.
	    newOrg notNil ifTrue:[
		(index ~~ 1) ifTrue:[  
		    newOrg y:(newOrg y + o1)
		].
	    ].
	    view pixelOrigin:newOrg corner:newCorner
"
	    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.
	]
    ]
!

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

    |pos delta|

    "/ setup all subviews to spread evenly ...

    pos := 0.0. 
    delta := 1.0 / (subViews size).

    1 to:(subViews size) 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
    ]
! !

!VariablePanel methodsFor:'private tableView protocol'!

setupSubviewOrigins
    "setup subviews origins (SV 16.1.95)"

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

    x := y := 0.0.

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

!VariablePanel class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg/Attic/VarPanel.st,v 1.12 1996-05-29 14:40:41 cg Exp $'
! !