VerticalPanelView.st
changeset 380 6eb402d01ae0
parent 341 7f5c67028a04
child 585 8f395aba0173
--- a/VerticalPanelView.st	Thu Feb 22 21:26:38 1996 +0100
+++ b/VerticalPanelView.st	Thu Feb 22 21:27:08 1996 +0100
@@ -640,210 +640,230 @@
 setChildPositions
     "(re)compute position of every child"
 
-    |ypos space sumOfHeights numChilds l hEach hInside maxWidth resizeToMax hL|
+    |ypos space sumOfHeights numChilds l hEach hInside maxWidth resizeToMax hL m2|
 
     subViews isNil ifTrue:[^ self].
 
     space := verticalSpace.
     numChilds := subViews size.
-    hInside := height - (margin * 2) + (borderWidth*2) - subViews last borderWidth.
+    m2 := margin * 2.
+    hInside := height - m2 + (borderWidth*2) - subViews last borderWidth.
 
     vLayout == #fitSpace ifTrue:[
-	"
-	 adjust childs extents and set origins.
-	 Be careful to avoid accumulation of rounding errors
-	"
-	hEach := (hInside - (numChilds + 1 * space)) / numChilds.
-	ypos := space + margin - borderWidth.
+        "
+         adjust childs extents and set origins.
+         Be careful to avoid accumulation of rounding errors
+        "
+        hEach := (hInside - (numChilds + 1 * space)) / numChilds.
+        ypos := space + margin - borderWidth.
     ] ifFalse:[
-	vLayout == #fit ifTrue:[
-	    "
-	     adjust childs extents and set origins.
-	     Be careful to avoid accumulation of rounding errors
-	    "
-	    hEach := (hInside - (numChilds - 1 * space)) / numChilds.
-	    ypos := margin - borderWidth.
-	] ifFalse:[
-	    "
-	     compute net height needed
-	    "
-	    sumOfHeights := subViews inject:0 into:[:sumSoFar :child | sumSoFar + child heightIncludingBorder].
+        vLayout == #fit ifTrue:[
+            "
+             adjust childs extents and set origins.
+             Be careful to avoid accumulation of rounding errors
+            "
+            hEach := (hInside - (numChilds - 1 * space)) / numChilds.
+            ypos := margin - borderWidth.
+        ] 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
-	    ].
-	    (l == #spread and:[numChilds == 1]) ifTrue:[
-		l := #spreadSpace
-	    ].
+            l := vLayout.
+            ((l == #center) and:[numChilds == 1]) ifTrue:[
+                l := #spread
+            ].
+            (l == #spread and:[numChilds == 1]) ifTrue:[
+                l := #spreadSpace
+            ].
 
-	    "
-	     compute position of topmost subview and space between them;
-	     if they do hardly fit, leave no space between them 
-	    "
-	    ((sumOfHeights >= (height - (margin * 2)))
-	    and:[l ~~ #fixTopSpace and:[l ~~ #fixTop]])  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 == #fixTopSpace ifTrue:[
-		    l := #topSpace
-		] ifFalse:[
-		    l == #fixTop ifTrue:[
-			l := #top 
-		    ]
-		].
-		((l == #bottom) or:[l == #bottomSpace]) ifTrue:[
-		    ypos := height - (space * (numChilds - 1)) - sumOfHeights.
-	"
-		    borderWidth == 0 ifTrue:[
-			ypos := ypos + space 
-		    ].
-	"           
-		    l == #bottomSpace ifTrue:[
-			ypos >= space ifTrue:[
-			    ypos := ypos - space
-			]
-		    ].
+            "
+             compute position of topmost subview and space between them;
+             if they do hardly fit, leave no space between them 
+            "
+            ((sumOfHeights >= (height - m2))
+            and:[l ~~ #fixTopSpace and:[l ~~ #fixTop]]) ifTrue:[
+                "
+                 if we have not enough space for all the elements, 
+                 fill them tight, and show what can be shown (at least)
+                "
+                ypos := margin.
+                space := 0
+            ] ifFalse:[
+                l == #fixTopSpace ifTrue:[
+                    l := #topSpace
+                ] ifFalse:[
+                    l == #fixTop ifTrue:[
+                        l := #top 
+                    ]
+                ].
+                ((l == #bottom) or:[l == #bottomSpace]) ifTrue:[
+                    ypos := height - (space * (numChilds - 1)) - 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 := 0.
-			(space == 0) ifTrue:[
-			    ypos := (height - sumOfHeights) // 2
-			]
-		    ] ifFalse: [
-		      (l == #spreadSpace) ifTrue:[
-			space := (height - sumOfHeights) // (numChilds + 1).
-			ypos := space.
-			(space == 0) ifTrue:[
-			    ypos := (height - sumOfHeights) // 2
-			]
-		      ] ifFalse: [
-			((l == #top)
-			or:[l == #topSpace
-			or:[l == #topFit
-			or:[l == #topSpaceFit]]]) ifTrue:[
-			    space := space min:(height - sumOfHeights) // (numChilds + 1).
-			    (vLayout == #fixTop or:[vLayout == #fixTopSpace]) ifTrue:[
-				space := space max:verticalSpace.
-			    ] ifFalse:[
-				space := space max:0.
-			    ].
-			    (l == #topSpace 
-			    or:[l == #topSpaceFit]) 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.
-			    ]
-			]
-		      ]
-		    ]
-		]
-	    ].
-	].
+                    ypos < 0 ifTrue:[
+                        space := space min:(height - sumOfHeights) // (numChilds + 1).
+                        ypos := height - (space * numChilds) - sumOfHeights.
+                    ]
+                ] ifFalse: [
+                    (l == #spread) ifTrue:[
+                        space := (height - m2 - sumOfHeights) // (numChilds - 1).
+                        ypos := margin.
+                        (space == 0) ifTrue:[
+                            ypos := (height - sumOfHeights) // 2
+                        ]
+                    ] ifFalse: [
+                      (l == #spreadSpace) ifTrue:[
+                        space := (height - sumOfHeights) // (numChilds + 1).
+                        ypos := space.
+                        (space == 0) ifTrue:[
+                            ypos := (height - sumOfHeights) // 2
+                        ]
+                      ] ifFalse: [
+                        ((l == #top)
+                        or:[l == #topSpace
+                        or:[l == #topFit
+                        or:[l == #topSpaceFit]]]) ifTrue:[
+                            space := space min:(height - sumOfHeights - m2) // (numChilds + 1).
+                            (vLayout == #fixTop or:[vLayout == #fixTopSpace]) ifTrue:[
+                                space := space max:verticalSpace.
+                            ] ifFalse:[
+                                space := space max:0.
+                            ].
+                            (l == #topSpace 
+                            or:[l == #topSpaceFit]) ifTrue:[
+                                ypos := space.
+                            ] ifFalse:[
+                                "/
+                                "/ if the very first view has a 0-level AND
+                                "/ my level is non-zero, begin with margin
+                                "/
+                                (margin ~~ 0 and:[subViews first level == 0]) ifTrue:[
+                                    ypos := margin
+                                ] 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.
+                            ]
+                        ]
+                      ]
+                    ]
+                ]
+            ].
+        ].
     ].
 
     hL := hLayout.
     resizeToMax := false.
     (hLayout endsWith:'Max') ifTrue:[
-	resizeToMax := true.
-	maxWidth := subViews inject:0 into:[:maxSoFar :child | maxSoFar max:child widthIncludingBorder].
-	hL == #centerMax ifTrue:[hL := #center].
-	hL == #rightMax ifTrue:[hL := #right].
-	hL == #rightSpaceMax ifTrue:[hL := #rightSpace].
-	hL == #leftMax ifTrue:[hL := #left].
-	hL == #leftSpaceMax ifTrue:[hL := #leftSpace].
+        resizeToMax := true.
+        maxWidth := subViews inject:0 into:[:maxSoFar :child | maxSoFar max:child widthIncludingBorder].
+        hL == #centerMax ifTrue:[hL := #center].
+        hL == #rightMax ifTrue:[hL := #right].
+        hL == #rightSpaceMax ifTrue:[hL := #rightSpace].
+        hL == #leftMax ifTrue:[hL := #left].
+        hL == #leftSpaceMax ifTrue:[hL := #leftSpace].
     ].
 
     "
      now set positions
     "
     subViews keysAndValuesDo:[:index :child |
-	|xpos bwChild wChild|
+        |xpos advance bwChild wChild newWChild|
 
-	wChild := child widthIncludingBorder.
-	bwChild := child borderWidth.
+        wChild := child widthIncludingBorder.
+        bwChild := child borderWidth.
 
-	resizeToMax ifTrue:[
-	    child width:(wChild := maxWidth - (bwChild  * 2)).
-	].
+        resizeToMax ifTrue:[
+            child width:(wChild := maxWidth - (bwChild  * 2)).
+        ].
 
-	hL == #left ifTrue:[
-	    xpos := 0
-	] ifFalse:[
-	    hL == #leftSpace ifTrue:[
-		xpos := horizontalSpace
-	    ] ifFalse:[
-		hL == #right ifTrue:[
-		    xpos := width - wChild
-		] ifFalse:[
-		    hL == #rightSpace ifTrue:[
-			xpos := width - horizontalSpace - wChild.
-		    ] ifFalse:[
-			hL == #fitSpace ifTrue:[
-			    xpos := horizontalSpace.
-			    child width:(width - (horizontalSpace +  bwChild * 2))
-			] ifFalse:[
-			    hL == #fit ifTrue:[
-				xpos := 0.
-				child width:(width - (bwChild  * 2))
-			    ] ifFalse:[
-				"centered"
-				 xpos := (width - wChild) // 2.
-			    ]
-			]
-		    ]
-		]
-	    ]
-	].
-	(xpos < 0) ifTrue:[ xpos := 0 ].
+        hL == #left ifTrue:[
+            xpos := 0
+        ] ifFalse:[
+            hL == #leftSpace ifTrue:[
+                xpos := horizontalSpace
+            ] ifFalse:[
+                hL == #right ifTrue:[
+                    xpos := width - wChild
+                ] ifFalse:[
+                    hL == #rightSpace ifTrue:[
+                        xpos := width - horizontalSpace - wChild.
+                    ] ifFalse:[
+                        hL == #fitSpace ifTrue:[
+                            xpos := horizontalSpace.
+                            newWChild := width - (horizontalSpace +  bwChild * 2)
+                        ] ifFalse:[
+                            hL == #fit ifTrue:[
+                                newWChild := width - (bwChild * 2).
+                                child level == 0 ifTrue:[
+                                    xpos := margin.
+                                    newWChild := newWChild - m2
+                                ] ifFalse:[
+                                    xpos := 0. 
+                                ].
+                            ] ifFalse:[
+                                "centered"
+                                 xpos := (width - m2 - wChild) // 2.
+                            ]
+                        ]
+                    ]
+                ]
+            ]
+        ].
+        newWChild notNil ifTrue:[
+            child width:newWChild
+        ].
 
-	(vLayout == #fit 
-	or:[vLayout == #fitSpace]) ifTrue:[
-	    child origin:(xpos @ ypos rounded)
-		  corner:(xpos + (child width - 1))
-			 @ (ypos + hEach - bwChild - 1) rounded.
-	    ypos := ypos + hEach + space
-	] ifFalse:[
-	    child origin:(xpos@ypos).
-	    ypos := ypos + (child heightIncludingBorder) + space
-	].
+        (xpos < 0) ifTrue:[ xpos := 0 ].
+
+        (vLayout == #fit 
+        or:[vLayout == #fitSpace]) ifTrue:[
+            child origin:(xpos @ ypos rounded)
+                  corner:(xpos + (child width - 1))
+                         @ (ypos + hEach - bwChild - 1) rounded.
+            advance := hEach
+        ] ifFalse:[
+            child origin:(xpos@ypos).
+            advance := child heightIncludingBorder
+        ].
+        ypos := ypos + advance + space.
 
-	index == numChilds ifTrue:[
-	    |y|
+        index == numChilds ifTrue:[
+            |y|
 
-	    vLayout == #topFit ifTrue:[
-		y := height - margin - 1.
-	    ].
-	    vLayout == #topSpaceFit ifTrue:[
-		y := height - margin - 1 - space
-	    ].
-	    y notNil ifTrue:[
-		subViews last corner:(xpos + child width - 1) @ y
-	    ]
-	]
+            (vLayout == #topFit or:[vLayout == #topSpaceFit]) ifTrue:[
+                y := height - margin - 1.
+                vLayout == #topSpaceFit ifTrue:[
+                    y := y - space
+                ].
+            ].
+            y notNil ifTrue:[
+                subViews last corner:(xpos + child width - 1) @ y
+            ]
+        ]
     ]
 
     "Modified: 4.9.1995 / 18:43:29 / claus"
+    "Modified: 22.2.1996 / 21:25:42 / cg"
 ! !
 
 !VerticalPanelView methodsFor:'queries'!
@@ -851,7 +871,7 @@
 preferredExtent
     "return a good extent, one that makes subviews fit"
 
-    |sumOfHeights maxWidth maxHeight|
+    |sumOfHeights maxWidth maxHeight m2|
 
     subViews isNil ifTrue:[^ horizontalSpace @ verticalSpace].
 
@@ -902,13 +922,14 @@
             maxWidth := maxWidth + (horizontalSpace * 2)
         ]        
     ].
-    ^ maxWidth @ sumOfHeights
+    m2 := margin * 2.
+    ^ (maxWidth + m2) @ (sumOfHeights + m2)
 
-    "Modified: 9.2.1996 / 18:56:07 / cg"
+    "Modified: 22.2.1996 / 21:14:02 / cg"
 ! !
 
 !VerticalPanelView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg/VerticalPanelView.st,v 1.19 1996-02-09 17:57:17 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg/VerticalPanelView.st,v 1.20 1996-02-22 20:27:08 cg Exp $'
 ! !