VarHPanel.st
author Claus Gittinger <cg@exept.de>
Mon, 23 Oct 1995 21:07:01 +0100
changeset 164 5ab02ff0d9ae
parent 105 3d064ba4a0cc
child 174 d80a6cc3f9b2
permissions -rw-r--r--
.

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

'From Smalltalk/X, Version:2.10.5 on 14-mar-1995 at 11:10:40 am'!

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

VariableHorizontalPanel comment:'
COPYRIGHT (c) 1992 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libwidg/Attic/VarHPanel.st,v 1.13 1995-03-18 05:16:26 claus Exp $
'!

!VariableHorizontalPanel class methodsFor:'documentation'!

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

version
"
$Header: /cvs/stx/stx/libwidg/Attic/VarHPanel.st,v 1.13 1995-03-18 05:16:26 claus Exp $
"
!

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

    The subvies dimensions MUST be given as relative sizes;
    typically creation is done as:

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

"
!

examples
"
   example:
	|top p v1 v2 v3|

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

	p := VariableHorizontalPanel 
		 origin:0.0 @ 0.0
		 corner:1.0 @ 1.0
		 in:top.
	v1 := SelectionInListView 
		 origin:0.0 @ 0.0
		 corner:0.5 @ 1.0
		 in:p.
	v2 := EditTextView 
		 origin:0.5 @ 0.0
		 corner:0.8 @ 1.0
		 in:p.
	v3 := ScrollableView 
		 for:TextView 
		 in:p.
	v3 origin:0.8 @ 0.0 
	   corner:1.0 @ 1.0.
	top open
"
! !

!VariableHorizontalPanel methodsFor:'private'!

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

    |y hh vDelta|

    subViews notNil ifTrue:[
	shadowForm notNil ifTrue:[
	    hh := shadowForm height
	] ifFalse:[
	    hh := barWidth
	].
	(handleStyle ~~ #normal and:[handleStyle ~~ #mswindows]) ifTrue:[
	    vDelta := barWidth // 2.
	] ifFalse:[
	    vDelta := 0
	].
	(handlePosition == #left) ifTrue:[
	    y := vDelta
	] ifFalse:[
	    (handlePosition == #right) ifTrue:[
		y := height - hh - margin - vDelta
	    ] ifFalse:[
		y := height - barWidth // 2
	    ]
	].
	(start + 1) to:stop do:[:index |
	    |x view|

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

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

    |step nSubviews|

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

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

            view pixelOrigin:newOrg extent:newExt.
        ]
    ]
!

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

    |x w |

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

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

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

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

setupSubviewOrigins
    "setup subviews origins (SV 16.1.95)"

    |x e|

    x := 0.0.

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

        view := subViews at:index.
        e := view relativeExtent.
        e notNil ifTrue:[
            view relativeExtent:nil.
            e := e x.
            index == subViews size ifTrue:[
                view origin:(x @ 0.0) corner:(1.0 @ 1.0)
            ] ifFalse:[
                view origin:(x @ 0.0) corner:((x+e) @ 1.0)
            ].
            x := x + e.
        ] ifFalse: [
            view origin:(x @ 0.0).
            x := view relativeCorner x.
        ].
    ]   

! !

!VariableHorizontalPanel methodsFor:'initializing'!

initCursor
    "set the cursor - a horizontal double arrow"

    DefaultCursor notNil ifTrue:[
	cursor := DefaultCursor
    ] 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"
	].
	DefaultCursor := cursor
    ]
!

defaultControllerClass
    ^ VariableHorizontalPanelController
! !

!VariableHorizontalPanel methodsFor:'drawing'!

drawHandleAtX:hx y:hy
    |w x m|

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

    self paint:viewBackground.
    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).

	    x := hx.
	    handleStyle == #st80 ifTrue:[
		x := x - 1.
	    ].
	    self drawEdgesForX:(x + m)
			     y:(hy - barWidth)
			 width:w 
			height:(barWidth + barWidth)
			 level:2.

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

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

        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.


! !