VerticalPanelView.st
changeset 1431 fd1e74d673ae
parent 1417 e9dffd6767a6
child 2031 6f28b9951713
--- a/VerticalPanelView.st	Tue Jan 27 19:06:10 1998 +0100
+++ b/VerticalPanelView.st	Tue Jan 27 21:15:43 1998 +0100
@@ -710,9 +710,9 @@
     subViews size == 0 ifTrue:[^ self].
 
     extentChanged ifTrue:[
-	ext := self computeExtent.
-	width := ext x.
-	height := ext y.
+        ext := self computeExtent.
+        width := ext x.
+        height := ext y.
     ].
 
     space := verticalSpace.
@@ -726,255 +726,256 @@
 
     resizeToMaxV := false.
     (vL endsWith:'Max') ifTrue:[
-	resizeToMaxV := true.
-	hEach := maxHeight := subViews inject:0 into:[:maxSoFar :child | maxSoFar max:child heightIncludingBorder].
-	vL := (vL copyWithoutLast:3) asSymbol.
+        resizeToMaxV := true.
+        hEach := maxHeight := subViews inject:0 into:[:maxSoFar :child | maxSoFar max:child heightIncludingBorder].
+        vL := (vL copyWithoutLast:3) asSymbol.
     ].
 
     numChilds == 1 ifTrue:[
-	(vL == #topFit or:[vL == #bottomFit]) ifTrue:[
-	    vL := #fit
-	].
-	(vL == #topSpaceFit or:[vL == #bottomSpaceFit]) ifTrue:[
-	    vL := #fitSpace
-	].
+        (vL == #topFit or:[vL == #bottomFit]) ifTrue:[
+            vL := #fit
+        ].
+        (vL == #topSpaceFit or:[vL == #bottomSpaceFit]) ifTrue:[
+            vL := #fitSpace
+        ].
     ].
 
     vL == #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:[
-	vL == #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:[
-	    l := vL.
+        vL == #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:[
+            l := vL.
 
-	    "/ adjust - do not include height of last(first) element if doing a fit
-	    (vL == #topFit or:[vL == #topSpaceFit]) ifTrue:[
-		subViews last height:0.
-	    ].
-	    (vL == #bottomFit or:[vL == #bottomSpaceFit]) ifTrue:[
-		subViews first height:0.
-	    ].
+            "/ adjust - do not include height of last(first) element if doing a fit
+            (vL == #topFit or:[vL == #topSpaceFit]) ifTrue:[
+                subViews last height:0.
+            ].
+            (vL == #bottomFit or:[vL == #bottomSpaceFit]) ifTrue:[
+                subViews first height:0.
+            ].
 
-	    "
-	     compute net height needed
-	    "
-	    resizeToMaxV ifTrue:[
-		sumOfHeights := subViews inject:0 into:[:sumSoFar :child | sumSoFar + maxHeight + (child borderWidth*2)].
-	    ] ifFalse:[
-		sumOfHeights := subViews inject:0 into:[:sumSoFar :child | sumSoFar + child heightIncludingBorder].
-	    ].
+            "
+             compute net height needed
+            "
+            resizeToMaxV ifTrue:[
+                sumOfHeights := subViews inject:0 into:[:sumSoFar :child | sumSoFar + maxHeight + (child borderWidth*2)].
+            ] ifFalse:[
+                sumOfHeights := subViews inject:0 into:[:sumSoFar :child | sumSoFar + child heightIncludingBorder].
+            ].
 
-	    restHeight := height - sumOfHeights.
+            restHeight := height - sumOfHeights.
 
-	    ((l == #center) and:[numChilds == 1]) ifTrue:[l := #spread].
-	    (l == #spread and:[numChilds == 1]) ifTrue:[l := #spreadSpace].
+            ((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 - 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
-		or:[l == #bottomFit or:[l == #bottomSpaceFit]]]) ifTrue:[
-		    ypos := restHeight - (space * (numChilds - 1)).
-	"
-		    borderWidth == 0 ifTrue:[
-			ypos := ypos + space 
-		    ].
-	"           
-		    (l == #bottomSpace
-		    or:[l == #bottomSpaceFit]) 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
+                or:[l == #bottomFit or:[l == #bottomSpaceFit]]]) ifTrue:[
+                    ypos := restHeight - (space * (numChilds - 1)).
+"/
+"/                    borderWidth == 0 ifTrue:[
+"/                        ypos := ypos + space 
+"/                    ].
+"/           
+                    (l == #bottomSpace
+                    or:[l == #bottomSpaceFit]) ifTrue:[
+                        ypos >= space ifTrue:[
+                            ypos := ypos - space
+                        ]
+                    ].
+                    ypos := ypos - margin.
 
-		    ypos < 0 ifTrue:[
-			space := space min:(restHeight // (numChilds + 1)).
-			ypos := restHeight - (space * numChilds).
-		    ]
-		] ifFalse: [
-		    (l == #spread) ifTrue:[
-			space := (restHeight - m2) // (numChilds - 1).
-			ypos := margin.
-			(space == 0) ifTrue:[
-			    ypos := restHeight // 2
-			]
-		    ] ifFalse: [
-		      (l == #spreadSpace) ifTrue:[
-			space := restHeight // (numChilds + 1).
-			ypos := space.
-			(space == 0) ifTrue:[
-			    ypos := restHeight // 2
-			]
-		      ] ifFalse: [
-			((l == #top) or:[l == #topSpace
-			or:[l == #topFit or:[l == #topSpaceFit]]]) ifTrue:[
-			    space := space min:(restHeight - m2) // (numChilds + 1).
-			    (vL == #fixTop or:[vL == #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 := (restHeight - ((numChilds - 1) * space)) // 2.
-			    ypos < 0 ifTrue:[
-				space := restHeight // (numChilds + 1).
-				ypos := (restHeight - ((numChilds - 1) * space)) // 2.
-			    ]
-			]
-		      ]
-		    ]
-		]
-	    ].
-	].
+                    ypos < 0 ifTrue:[
+                        space := space min:(restHeight // (numChilds + 1)).
+                        ypos := restHeight - (space * numChilds).
+                    ]
+                ] ifFalse: [
+                    (l == #spread) ifTrue:[
+                        space := (restHeight - m2) // (numChilds - 1).
+                        ypos := margin.
+                        (space == 0) ifTrue:[
+                            ypos := restHeight // 2
+                        ]
+                    ] ifFalse: [
+                      (l == #spreadSpace) ifTrue:[
+                        space := (restHeight - m2) // (numChilds + 1).
+                        ypos := space + margin.
+                        (space == 0) ifTrue:[
+                            ypos := restHeight // 2
+                        ]
+                      ] ifFalse: [
+                        ((l == #top) or:[l == #topSpace
+                        or:[l == #topFit or:[l == #topSpaceFit]]]) ifTrue:[
+                            space := space min:(restHeight - m2) // (numChilds + 1).
+                            (vL == #fixTop or:[vL == #fixTopSpace]) ifTrue:[
+                                space := space max:verticalSpace.
+                            ] ifFalse:[
+                                space := space max:0.
+                            ].
+                            (l == #topSpace or:[l == #topSpaceFit]) ifTrue:[
+                                ypos := space + margin.
+                            ] ifFalse:[
+                                "/
+                                "/ if the very first view has a 0-level AND
+                                "/ my level is non-zero, begin with margin
+                                "/
+                                true "(margin ~~ 0 and:[subViews first level == 0])" ifTrue:[
+                                    ypos := margin
+                                ] ifFalse:[
+                                    ypos := 0
+                                ]
+                            ]
+                        ] ifFalse:[
+                            "center"
+                            ypos := (restHeight - ((numChilds - 1) * space)) // 2.
+                            ypos < 0 ifTrue:[
+                                space := restHeight // (numChilds + 1).
+                                ypos := (restHeight - ((numChilds - 1) * space)) // 2.
+                            ]
+                        ]
+                      ]
+                    ]
+                ]
+            ].
+        ].
     ].
 
     resizeToMaxH := false.
     (hL endsWith:'Max') ifTrue:[
-	resizeToMaxH := true.
-	maxWidth := subViews inject:0 into:[:maxSoFar :child | maxSoFar max:child widthIncludingBorder].
-	hL := (hL copyWithoutLast:3) asSymbol.
+        resizeToMaxH := true.
+        maxWidth := subViews inject:0 into:[:maxSoFar :child | maxSoFar max:child widthIncludingBorder].
+        hL := (hL copyWithoutLast:3) asSymbol.
     ].
 
     "
      now set positions
     "
     subViews keysAndValuesDo:[:index :child |
-	|xpos advance bwChild wChild newWChild x2|
+        |xpos advance bwChild wChild newWChild x2|
 
-	wChild := child widthIncludingBorder.
-	bwChild := child borderWidth.
+        wChild := child widthIncludingBorder.
+        bwChild := child borderWidth.
 
-	resizeToMaxH ifTrue:[
-	    child width:(wChild := maxWidth - (bwChild  * 2)).
-	].
+        resizeToMaxH ifTrue:[
+            child width:(wChild := maxWidth - (bwChild  * 2)).
+        ].
 
-	hL == #left ifTrue:[
-	    xpos := 0 - borderWidth.
-	] 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)".
-				borderWidth == 0 ifTrue:[
-				    newWChild :=  newWChild - (bwChild * 2)
-				].
-				child level == 0 ifTrue:[
-				    xpos := margin - borderWidth.
-				    newWChild := newWChild - m2
-				] ifFalse:[
-				    xpos := 0 - borderWidth. 
-				].
-			    ] ifFalse:[
-				"centered"
-				 xpos := (width - m2 - wChild) // 2.
-			    ]
-			]
-		    ]
-		]
-	    ]
-	].
-	newWChild notNil ifTrue:[
-	    child width:newWChild
-	].
+        hL == #left ifTrue:[
+            xpos := 0 - borderWidth + margin.
+        ] ifFalse:[
+            hL == #leftSpace ifTrue:[
+                xpos := horizontalSpace + margin
+            ] ifFalse:[
+                hL == #right ifTrue:[
+                    xpos := width - wChild - margin
+                ] ifFalse:[
+                    hL == #rightSpace ifTrue:[
+                        xpos := width - horizontalSpace - wChild - margin.
+                    ] ifFalse:[
+                        hL == #fitSpace ifTrue:[
+                            xpos := horizontalSpace + margin.
+                            newWChild := width - m2 - (horizontalSpace + bwChild * 2)
+                        ] ifFalse:[
+                            hL == #fit ifTrue:[
+                                newWChild := width "- (bwChild * 2)".
+                                borderWidth == 0 ifTrue:[
+                                    newWChild :=  newWChild - (bwChild * 2)
+                                ].
+                                true "child level == 0" ifTrue:[
+                                    xpos := margin - borderWidth.
+                                    newWChild := newWChild - m2
+                                ] ifFalse:[
+                                    xpos := 0 - borderWidth. 
+                                ].
+                            ] ifFalse:[
+                                "centered"
+                                 xpos := margin + ((width - m2 - wChild) // 2).
+                            ]
+                        ]
+                    ]
+                ]
+            ]
+        ].
+        newWChild notNil ifTrue:[
+            child width:newWChild
+        ].
 
 "/        (xpos < 0) ifTrue:[ xpos := 0 ].
 
-	x2 := xpos + (child widthIncludingBorder - 1).
+        x2 := xpos + (child widthIncludingBorder - 1).
 
-	(vL == #fit 
-	or:[vL == #fitSpace
-	or:[resizeToMaxV]]) ifTrue:[
-	    child origin:(xpos @ ypos rounded)
-		  corner:(x2 @ (ypos + hEach - bwChild - 1) rounded).
-	    advance := hEach
-	] ifFalse:[
-	    child origin:(xpos@ypos).
-	    advance := child heightIncludingBorder
-	].
+        (vL == #fit 
+        or:[vL == #fitSpace
+        or:[resizeToMaxV]]) ifTrue:[
+            child origin:(xpos @ ypos rounded)
+                  corner:(x2 @ (ypos + hEach - bwChild - 1) rounded).
+            advance := hEach
+        ] ifFalse:[
+            child origin:(xpos@ypos).
+            advance := child heightIncludingBorder
+        ].
 
-	index == numChilds ifTrue:[
-	    |y|
+        index == numChilds ifTrue:[
+            |y|
 
-	    (vL == #topFit or:[vL == #topSpaceFit]) ifTrue:[
-		y := height - margin - 1.
-		vL == #topSpaceFit ifTrue:[
-		    y := y - space
-		].
-		child corner:x2 @ y
-	    ].
-	].
-	index == 1 ifTrue:[
-	    |y yB|
+            (vL == #topFit or:[vL == #topSpaceFit]) ifTrue:[
+                y := height - margin - 1.
+                vL == #topSpaceFit ifTrue:[
+                    y := y - space
+                ].
+                child corner:x2 @ y
+            ].
+        ].
+        index == 1 ifTrue:[
+            |y yB|
 
-	    (vL == #bottomFit or:[vL == #bottomSpaceFit]) ifTrue:[
-		y := 0 + (child borderWidth * 2) - borderWidth.
-		vL == #bottomSpaceFit ifTrue:[
-		    y := y + space
-		].
-		yB := child corner y.
-		child origin:((child origin x) @ y)
-		      corner:((child corner x) @ yB)
-	    ].
-	].
+            (vL == #bottomFit or:[vL == #bottomSpaceFit]) ifTrue:[
+                y := margin + 0 + (child borderWidth * 2) - borderWidth.
+                vL == #bottomSpaceFit ifTrue:[
+                    y := y + space
+                ].
+                yB := child corner y.
+                child origin:((child origin x) @ y)
+                      corner:((child corner x) @ yB)
+            ].
+        ].
 
-	ypos := ypos + advance + space.
+        ypos := ypos + advance + space.
     ]
 
     "Modified: / 4.9.1995 / 18:43:29 / claus"
-    "Modified: / 17.1.1998 / 00:17:52 / cg"
+    "Modified: / 27.1.1998 / 21:14:32 / cg"
 ! !
 
 !VerticalPanelView methodsFor:'queries'!
@@ -1053,5 +1054,5 @@
 !VerticalPanelView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg/VerticalPanelView.st,v 1.33 1998-01-17 13:47:58 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg/VerticalPanelView.st,v 1.34 1998-01-27 20:15:43 cg Exp $'
 ! !