VerticalPanelView.st
changeset 63 f4eaf04d1eaf
parent 59 450ce95a72a4
child 65 b33e4f3a264e
--- a/VerticalPanelView.st	Thu Nov 17 15:34:12 1994 +0100
+++ b/VerticalPanelView.st	Thu Nov 17 15:38:53 1994 +0100
@@ -21,7 +21,7 @@
 COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libwidg/VerticalPanelView.st,v 1.5 1994-10-10 03:03:18 claus Exp $
+$Header: /cvs/stx/stx/libwidg/VerticalPanelView.st,v 1.6 1994-11-17 14:38:46 claus Exp $
 '!
 
 !VerticalPanelView class methodsFor:'documentation'!
@@ -42,16 +42,45 @@
 
 version
 "
-$Header: /cvs/stx/stx/libwidg/VerticalPanelView.st,v 1.5 1994-10-10 03:03:18 claus Exp $
+$Header: /cvs/stx/stx/libwidg/VerticalPanelView.st,v 1.6 1994-11-17 14:38:46 claus Exp $
 "
 !
 
 documentation
 "
     a View which arranges its child-views in a vertical column.
-    All real work is done in PanelView - only the layout computation is
+    All real work is done in PanelView - except the layout computation is
     redefined here.
 
+    The layout is controlled by two instance variables. 
+    The vertical layout can be any of:
+
+	#top            arrange elements at the top
+	#topSpace       arrange elements at the top, start with spacing
+	#bottom         arrange elements at the bottom
+	#bottomSpace    arrange elements at the bottom, start with spacing
+	#center         arrange elements in the center
+	#spread         spread elements evenly
+	#fit            like spread, but resize elements for tight packing
+
+    the horizontal layout can be:
+
+	#left           place element at the left
+	#leftSpace      place element at the left, offset by horizontalSpace
+	#center         place it horizontally centered
+	#right          place it at the right
+	#rightSpace     place it at the right, offset by horizontalSpace
+	#fit            resize elements horizontally to fit this panel
+
+    The defaults is #centered for both directions.
+    The layout is changed by the messages #verticalLayout: and #horizontalLayout:.
+    For backward compatibility (to times, where only vLayout existed), the simple
+    #layout: does the same as #verticalLayout:. Do not use this old method.
+"
+!
+
+examples
+"
     example: default layout (centered)
 
 	|v p b1 b2 b3|
@@ -66,13 +95,13 @@
 	v open
 
 
-    example: left-layout
+    example: top-layout
 
 	|v p b1 b2 b3|
 
 	v := StandardSystemView new.
 	p := VerticalPanelView in:v.
-	p layout:#top.
+	p verticalLayout:#top.
 	p origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).
 	b1 := Button label:'button1' in:p.
 	b2 := Button label:'button2' in:p.
@@ -81,13 +110,13 @@
 	v open
 
 
-    example: right-layout
+    example: bottom-layout
 
 	|v p b1 b2 b3|
 
 	v := StandardSystemView new.
 	p := VerticalPanelView in:v.
-	p layout:#bottom.
+	p verticalLayout:#bottom.
 	p origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).
 	b1 := Button label:'button1' in:p.
 	b2 := Button label:'button2' in:p.
@@ -102,16 +131,132 @@
 
 	v := StandardSystemView new.
 	p := VerticalPanelView in:v.
-	p layout:#spread.
+	p verticalLayout:#spread.
+	p origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).
+	b1 := Button label:'button1' in:p.
+	b2 := Button label:'button2' in:p.
+	b3 := Button label:'button3' in:p.
+	v extent:100 @ 300.
+	v open
+
+    example: from top, each at left:
+
+	|v p b1 b2 b3|
+
+	v := StandardSystemView new.
+	p := VerticalPanelView in:v.
+	p verticalLayout:#top.
+	p horizontalLayout:#left.
+	p origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).
+	b1 := Button label:'button1' in:p.
+	b2 := Button label:'button2' in:p.
+	b3 := Button label:'button3' in:p.
+	v extent:100 @ 300.
+	v open
+
+    example: centered, right:
+
+	|v p b1 b2 b3|
+
+	v := StandardSystemView new.
+	p := VerticalPanelView in:v.
+	p verticalLayout:#centered.
+	p horizontalLayout:#right.
 	p origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).
 	b1 := Button label:'button1' in:p.
 	b2 := Button label:'button2' in:p.
 	b3 := Button label:'button3' in:p.
 	v extent:100 @ 300.
 	v open
+
+    you should try more examples, combining spacing and different
+    verticalLayout:/horizontalLayout: combinations.
 "
 ! !
 
+!VerticalPanelView methodsFor:'accessing'!
+
+horizontalLayout
+    "return the horizontal layout as symbol.
+     the returned value is one of
+	#left 
+	#leftSpace 
+	#center
+	#right 
+	#rightSpace 
+	#fit 
+      the default is #centered
+    "
+
+    ^ hLayout
+!
+
+verticalLayout
+    "return the vertical layout as a symbol.
+     the returned value is one of
+	#top
+	#topSpace
+	#spread
+	#fit
+	#center
+	#bottom
+	#bottomSpace
+      the default is #centered
+    "
+
+    ^ vLayout
+!
+
+horizontalLayout:aSymbol
+    "change the horizontal layout as symbol.
+     The argument, aSymbol must be one of:
+	#left 
+	#leftSpace 
+	#center
+	#right 
+	#rightSpace 
+	#fit 
+      the default (if never changed) is #centered
+    "
+
+    (hLayout ~~ aSymbol) ifTrue:[
+	hLayout := aSymbol.
+	self layoutChanged
+    ]
+!
+
+verticalLayout:aSymbol
+    "change the vertical layout as a symbol.
+     The argument, aSymbol must be one of:
+	#top
+	#topSpace
+	#spread
+	#fit
+	#center
+	#bottom
+	#bottomSpace
+      the default (if never changed) is #centered
+    "
+
+    (vLayout ~~ aSymbol) ifTrue:[
+	vLayout := aSymbol.
+	self layoutChanged
+    ]
+!
+
+layout
+    "leftover for historic reasons - do not use any more"
+
+    self verticalLayout
+!
+
+layout:aSymbol
+    "leftover for historic reasons - do not use any more"
+
+    self verticalLayout:aSymbol
+! !
+
+
 !VerticalPanelView methodsFor:'queries'!
 
 preferedExtent
@@ -127,9 +272,16 @@
     maxWidth := 0.
 
     subViews do:[:child |
-	sumOfHeights := sumOfHeights + child heightIncludingBorder.
-	maxWidth := maxWidth max:(child widthIncludingBorder).
-	maxHeight := maxHeight max:(child heightIncludingBorder).
+	|childsPreference|
+
+	childsPreference := child preferedExtent.
+	sumOfHeights := sumOfHeights + childsPreference y.
+	maxHeight := maxHeight max:childsPreference y.
+	maxWidth := maxWidth max:childsPreference x.
+
+"/        sumOfHeights := sumOfHeights + child heightIncludingBorder.
+"/        maxWidth := maxWidth max:(child widthIncludingBorder).
+"/        maxHeight := maxHeight max:(child heightIncludingBorder).
     ].
     borderWidth ~~ 0 ifTrue:[
 	sumOfHeights := sumOfHeights + (horizontalSpace * 2).
@@ -145,98 +297,137 @@
 setChildPositions
     "(re)compute position of every child"
 
-    |xpos ypos space sumOfHeights numChilds l hEach|
+    |ypos space sumOfHeights numChilds l hEach|
 
     subViews isNil ifTrue:[^ self].
 
     space := verticalSpace.
+    numChilds := subViews size.
 
-    numChilds := subViews size.
-    layout == #fit ifTrue:[
+    vLayout == #fit ifTrue:[
 	"
 	 adjust childs extents and set origins.
 	 Be careful to avoid accumulation of rounding errors
 	"
 	hEach := (height - (margin * 2) - (numChilds + 1 * space) + borderWidth) / numChilds.
 	ypos := space + margin - borderWidth.
-	subViews do:[:child |
-	    xpos := (width - child widthIncludingBorder) // 2.
-	    (xpos < 0) ifTrue:[xpos := 0].
+    ] ifFalse:[
+
+	"
+	 compute net height needed
+	"
+	sumOfHeights := subViews inject:0 into:[:sumSoFar :child | sumSoFar + child heightIncludingBorder].
+
+	l := vLayout.
+	((l == #center) and:[numChilds == 1]) ifTrue:[
+	    l := #spread
+	].
+
+	"
+	 compute position of topmost subview and space between them;
+	 if they do hardly fit, leave no space between them 
+	"
+	(sumOfHeights >= (height - (margin * 2))) ifTrue:[
+	    "
+	     if we  have not enough space for all the elements, 
+	     fill them tight, and show what can be shown (at least)
+	    "
+	    ypos := 0.
+	    space := 0
+	] ifFalse:[
+	    ((l == #bottom) or:[l == #bottomSpace]) ifTrue:[
+		ypos := height - (space * numChilds) - sumOfHeights.
+    "
+		borderWidth == 0 ifTrue:[
+		    ypos := ypos + space 
+		].
+    "           
+		l == #bottomSpace ifTrue:[
+		    ypos > space ifTrue:[
+			ypos := ypos - space
+		    ]
+		].
 
+		ypos < 0 ifTrue:[
+		    space := space min:(height - sumOfHeights) // (numChilds + 1).
+		    ypos := height - (space * numChilds) - sumOfHeights.
+		]
+	    ] ifFalse: [
+		(l == #spread) ifTrue:[
+		    space := (height - sumOfHeights) // (numChilds + 1).
+		    ypos := space.
+		    (space == 0) ifTrue:[
+			ypos := (height - sumOfHeights) // 2
+		    ]
+		] ifFalse: [
+		    ((l == #top) or:[l == #topSpace]) ifTrue:[
+    "
+			borderWidth == 0 ifTrue:[
+			    ypos := 0
+			] ifFalse:[
+			    ypos := verticalSpace
+			].
+    "
+			space := space min:(height - sumOfHeights) // (numChilds + 1).
+			l == #topSpace ifTrue:[
+			    ypos := space.
+			] ifFalse:[
+			    ypos := 0
+			]
+		    ] ifFalse:[
+			"center"
+			ypos := (height - (sumOfHeights
+					     + ((numChilds - 1) * space))) // 2.
+			ypos < 0 ifTrue:[
+			    space := (height - sumOfHeights) // (numChilds + 1).
+			    ypos := (height - (sumOfHeights
+					   + ((numChilds - 1) * space))) // 2.
+			]
+		    ]
+		]
+	    ]
+	].
+    ].
+
+    "
+     now set positions
+    "
+    subViews do:[:child |
+	|xpos|
+
+	hLayout == #left ifTrue:[
+	    xpos := 0
+	] ifFalse:[
+	    hLayout == #leftSpace ifTrue:[
+		xpos := horizontalSpace
+	    ] ifFalse:[
+		hLayout == #right ifTrue:[
+		    xpos := width - child widthIncludingBorder
+		] ifFalse:[
+		    hLayout == #rightSpace ifTrue:[
+			xpos := width - horizontalSpace - child widthIncludingBorder.
+		    ] ifFalse:[
+			hLayout == #fit ifTrue:[
+			    xpos := horizontalSpace.
+			    child width:(width - (horizontalSpace + child borderWidth * 2))
+			] ifFalse:[
+			   "centered"
+			    xpos := (width - child widthIncludingBorder) // 2.
+			]
+		    ]
+		]
+	    ]
+	].
+	(xpos < 0) ifTrue:[ xpos := 0 ].
+
+	vLayout == #fit ifTrue:[
 	    child origin:(xpos @ ypos rounded)
 		  corner:(xpos + (child width))
 			 @ (ypos + hEach - (child borderWidth)) rounded.
 	    ypos := ypos + hEach + "(child borderWidth * 2) +" space
-	].
-	^ self
-    ].
-
-    "compute net height needed"
-
-    sumOfHeights := subViews inject:0 into:[:sumSoFar :child | sumSoFar + child heightIncludingBorder].
-
-    l := layout.
-    ((l == #center) and:[numChilds == 1]) ifTrue:[
-	l := #spread
-    ].
-
-    "compute position of topmost subview and space between them;
-     if they do hardly fit, leave no space between them "
-
-    (sumOfHeights >= (height - (margin * 2))) ifTrue:[
-	ypos := 0.
-	space := 0
-    ] ifFalse:[
-	(l == #bottom) ifTrue:[
-	    ypos := height - (space * numChilds) - sumOfHeights.
-"
-	    borderWidth == 0 ifTrue:[
-		ypos := ypos + space 
-	    ].
-"
-	    ypos < 0 ifTrue:[
-		space := space min:(height - sumOfHeights) // (numChilds + 1).
-		ypos := height - (space * numChilds) - sumOfHeights.
-	    ]
-	] ifFalse: [
-	    (l == #spread) ifTrue:[
-		space := (height - sumOfHeights) // (numChilds + 1).
-		ypos := space.
-		(space == 0) ifTrue:[
-		    ypos := (height - sumOfHeights) // 2
-		]
-	    ] ifFalse: [
-		(l == #center) ifTrue:[
-		    ypos := (height - (sumOfHeights
-				       + ((numChilds - 1) * space))) // 2.
-		    ypos < 0 ifTrue:[
-			space := (height - sumOfHeights) // (numChilds + 1).
-			ypos := (height - (sumOfHeights
-				       + ((numChilds - 1) * space))) // 2.
-		    ]
-		] ifFalse:[
-"
-		    borderWidth == 0 ifTrue:[
-			ypos := 0
-		    ] ifFalse:[
-			ypos := verticalSpace
-		    ].
-"
-		    space := space min:(height - sumOfHeights) // (numChilds + 1).
-		    ypos := space.
-		]
-	    ]
+	] ifFalse:[
+	    child origin:(xpos@ypos).
+	    ypos := ypos + (child heightIncludingBorder) + space
 	]
-    ].
-
-
-    "now set positions"
-
-    subViews do:[:childView |
-	xpos := (width - childView widthIncludingBorder) // 2.
-	(xpos < 0) ifTrue:[ xpos := 0 ].
-
-	childView origin:(xpos@ypos).
-	ypos := ypos + (childView heightIncludingBorder) + space
     ]
 ! !