MultiColumnPanelView.st
changeset 4564 0a0d41148e11
parent 4019 bf57f58f13a8
child 6487 debe1f7cce35
--- a/MultiColumnPanelView.st	Thu Apr 25 15:09:59 2013 +0200
+++ b/MultiColumnPanelView.st	Thu Apr 25 15:10:34 2013 +0200
@@ -273,9 +273,7 @@
 setChildPositions
     "(re)compute position of every child"
 
-    |xpos ypos space sumOfHeights numChilds l hEach hInside hL vL
-     maxWidth maxHeight resizeToMaxV resizeToMaxH m2 subViews restHeight
-     rowsPerCol maxWidthPerCol col numCols cX cY bw|
+    |xpos ypos space numChilds hInside hL vL maxHeight m2 subViews rowsPerCol maxWidthPerCol col numCols cX cY bw|
 
     subViews := self subViewsToConsider.
     subViews size == 0 ifTrue:[^ self].
@@ -342,262 +340,262 @@
 
 "/ old
 
-    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.
-    ].
-
-    numChilds == 1 ifTrue:[
-        (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 - bw.
-    ] 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 - bw.
-        ] ifFalse:[
-            l := vL.
-
-            "
-             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].
-
-                "/ adjust - do not include height of last(first) element if doing a fit
-                (vL == #topFit or:[vL == #topSpaceFit]) ifTrue:[
-                    sumOfHeights := sumOfHeights - subViews last heightIncludingBorder.
-                ] ifFalse:[
-                    (vL == #bottomFit or:[vL == #bottomSpaceFit]) ifTrue:[
-                        sumOfHeights := sumOfHeights - subViews first heightIncludingBorder.
-                    ]
-                ].
-            ].
-
-            restHeight := height - sumOfHeights - ((numChilds-1)*space).
-
-            ((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)).
+"/    resizeToMaxV := false.
+"/    (vL endsWith:'Max') ifTrue:[
+"/        resizeToMaxV := true.
+"/        hEach := maxHeight := subViews inject:0 into:[:maxSoFar :child | maxSoFar max:child heightIncludingBorder].
+"/        vL := (vL copyButLast:3) asSymbol.
+"/    ].
+"/
+"/    numChilds == 1 ifTrue:[
+"/        (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 - bw.
+"/    ] 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 - bw.
+"/        ] ifFalse:[
+"/            l := vL.
+"/
+"/            "
+"/             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].
 "/
-"/                    bw == 0 ifTrue:[
-"/                        ypos := ypos + space 
+"/                "/ adjust - do not include height of last(first) element if doing a fit
+"/                (vL == #topFit or:[vL == #topSpaceFit]) ifTrue:[
+"/                    sumOfHeights := sumOfHeights - subViews last heightIncludingBorder.
+"/                ] ifFalse:[
+"/                    (vL == #bottomFit or:[vL == #bottomSpaceFit]) ifTrue:[
+"/                        sumOfHeights := sumOfHeights - subViews first heightIncludingBorder.
+"/                    ]
+"/                ].
+"/            ].
+"/
+"/            restHeight := height - sumOfHeights - ((numChilds-1)*space).
+"/
+"/            ((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)).
+"/"/
+"/"/                    bw == 0 ifTrue:[
+"/"/                        ypos := ypos + space 
+"/"/                    ].
+"/"/           
+"/                    (l == #bottomSpace
+"/                    or:[l == #bottomSpaceFit]) ifTrue:[
+"/                        ypos >= space 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 - 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.
-    ].
-
-    "
-     now set positions
-    "
-    subViews keysAndValuesDo:[:index :child |
-        |xpos advance bwChild wChild newWChild x2|
-
-        wChild := child widthIncludingBorder.
-        bwChild := child borderWidth.
-
-        elementsChangeSize ifTrue:[
-            "to avoid a recursion when we change the elements size"
-            child removeDependent:self.
-        ].
-        resizeToMaxH ifTrue:[
-            child width:(wChild := maxWidth - (bwChild  * 2)).
-        ].
-
-        hL == #left ifTrue:[
-            xpos := 0 - bw + 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)".
-                                bw == 0 ifTrue:[
-                                    newWChild :=  newWChild - (bwChild * 2)
-                                ].
-                                true "child level == 0" ifTrue:[
-                                    xpos := margin - bw.
-                                    newWChild := newWChild - m2
-                                ] ifFalse:[
-                                    xpos := 0 - bw. 
-                                ].
-                            ] ifFalse:[
-                                "centered"
-                                 xpos := margin + ((width - m2 - wChild) // 2).
-                            ]
-                        ]
-                    ]
-                ]
-            ]
-        ].
-        newWChild notNil ifTrue:[
-            child width:newWChild
-        ].
-
-"/        (xpos < 0) ifTrue:[ xpos := 0 ].
-
-        x2 := xpos + child width - 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
-        ].
-
-        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:[
-            (vL == #bottomFit or:[vL == #bottomSpaceFit]) ifTrue:[
-                ypos := margin + 0 + (child borderWidth * 2) - bw.
-                vL == #bottomSpaceFit ifTrue:[
-                    ypos := ypos + space
-                ].
-                advance := restHeight.
-                child origin:((child origin x) @ ypos)
-                      corner:((child corner x) @ (ypos+advance))
-            ].
-        ].
-
-        ypos := ypos + advance + space.
-        elementsChangeSize ifTrue:[
-            "reinstall dependency that we removed above"
-            child addDependent:self.
-        ].
-    ]
+"/                    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 - 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.
+"/    ].
+"/
+"/    "
+"/     now set positions
+"/    "
+"/    subViews keysAndValuesDo:[:index :child |
+"/        |xpos advance bwChild wChild newWChild x2|
+"/
+"/        wChild := child widthIncludingBorder.
+"/        bwChild := child borderWidth.
+"/
+"/        elementsChangeSize ifTrue:[
+"/            "to avoid a recursion when we change the elements size"
+"/            child removeDependent:self.
+"/        ].
+"/        resizeToMaxH ifTrue:[
+"/            child width:(wChild := maxWidth - (bwChild  * 2)).
+"/        ].
+"/
+"/        hL == #left ifTrue:[
+"/            xpos := 0 - bw + 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)".
+"/                                bw == 0 ifTrue:[
+"/                                    newWChild :=  newWChild - (bwChild * 2)
+"/                                ].
+"/                                true "child level == 0" ifTrue:[
+"/                                    xpos := margin - bw.
+"/                                    newWChild := newWChild - m2
+"/                                ] ifFalse:[
+"/                                    xpos := 0 - bw. 
+"/                                ].
+"/                            ] ifFalse:[
+"/                                "centered"
+"/                                 xpos := margin + ((width - m2 - wChild) // 2).
+"/                            ]
+"/                        ]
+"/                    ]
+"/                ]
+"/            ]
+"/        ].
+"/        newWChild notNil ifTrue:[
+"/            child width:newWChild
+"/        ].
+"/
+"/"/        (xpos < 0) ifTrue:[ xpos := 0 ].
+"/
+"/        x2 := xpos + child width - 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
+"/        ].
+"/
+"/        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:[
+"/            (vL == #bottomFit or:[vL == #bottomSpaceFit]) ifTrue:[
+"/                ypos := margin + 0 + (child borderWidth * 2) - bw.
+"/                vL == #bottomSpaceFit ifTrue:[
+"/                    ypos := ypos + space
+"/                ].
+"/                advance := restHeight.
+"/                child origin:((child origin x) @ ypos)
+"/                      corner:((child corner x) @ (ypos+advance))
+"/            ].
+"/        ].
+"/
+"/        ypos := ypos + advance + space.
+"/        elementsChangeSize ifTrue:[
+"/            "reinstall dependency that we removed above"
+"/            child addDependent:self.
+"/        ].
+"/    ]
 
     "Modified: / 04-09-1995 / 18:43:29 / claus"
     "Modified: / 10-10-2007 / 13:47:56 / cg"
@@ -676,9 +674,10 @@
 !MultiColumnPanelView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg/MultiColumnPanelView.st,v 1.3 2009-10-23 15:22:19 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg/MultiColumnPanelView.st,v 1.4 2013-04-25 13:10:34 stefan Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libwidg/MultiColumnPanelView.st,v 1.3 2009-10-23 15:22:19 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg/MultiColumnPanelView.st,v 1.4 2013-04-25 13:10:34 stefan Exp $'
 ! !
+