VPanelV.st
changeset 125 3ffa271732f7
parent 77 565b052f5277
child 127 462396b08e30
--- a/VPanelV.st	Mon May 08 17:19:27 1995 +0200
+++ b/VPanelV.st	Tue May 09 03:57:16 1995 +0200
@@ -10,18 +10,20 @@
  hereby transferred.
 "
 
+'From Smalltalk/X, Version:2.10.5 on 9-may-1995 at 12:07:08 pm'!
+
 PanelView subclass:#VerticalPanelView
-       instanceVariableNames:''
-       classVariableNames:''
-       poolDictionaries:''
-       category:'Views-Layout'
+	 instanceVariableNames:''
+	 classVariableNames:''
+	 poolDictionaries:''
+	 category:'Views-Layout'
 !
 
 VerticalPanelView comment:'
 COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libwidg/Attic/VPanelV.st,v 1.8 1995-02-06 00:53:30 claus Exp $
+$Header: /cvs/stx/stx/libwidg/Attic/VPanelV.st,v 1.9 1995-05-09 01:57:00 claus Exp $
 '!
 
 !VerticalPanelView class methodsFor:'documentation'!
@@ -42,7 +44,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libwidg/Attic/VPanelV.st,v 1.8 1995-02-06 00:53:30 claus Exp $
+$Header: /cvs/stx/stx/libwidg/Attic/VPanelV.st,v 1.9 1995-05-09 01:57:00 claus Exp $
 "
 !
 
@@ -98,375 +100,256 @@
 
     example: default layout (centered)
 
-	|v p b1 b2 b3|
+        |v p b1 b2 b3|
 
-	v := StandardSystemView new.
-	p := VerticalPanelView in:v.
-	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
+        v := StandardSystemView new.
+        p := VerticalPanelView in:v.
+        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: top-layout
 
-	|v p b1 b2 b3|
+        |v p b1 b2 b3|
 
-	v := StandardSystemView new.
-	p := VerticalPanelView in:v.
-	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.
-	b3 := Button label:'button3' in:p.
-	v extent:100 @ 300.
-	v open
+        v := StandardSystemView new.
+        p := VerticalPanelView in:v.
+        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.
+        b3 := Button label:'button3' in:p.
+        v extent:100 @ 300.
+        v open
 
 
     example: top-layout; horizontal fit
 
-	|v p b1 b2 b3|
+        |v p b1 b2 b3|
 
-	v := StandardSystemView new.
-	p := VerticalPanelView in:v.
-	p verticalLayout:#top.
-	p horizontalLayout:#fit.
-	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
+        v := StandardSystemView new.
+        p := VerticalPanelView in:v.
+        p verticalLayout:#top.
+        p horizontalLayout:#fit.
+        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: top-layout; horizontal fit with space
 
-	|v p b1 b2 b3|
+        |v p b1 b2 b3|
 
-	v := StandardSystemView new.
-	p := VerticalPanelView in:v.
-	p verticalLayout:#top.
-	p horizontalLayout:#fitSpace.
-	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
+        v := StandardSystemView new.
+        p := VerticalPanelView in:v.
+        p verticalLayout:#top.
+        p horizontalLayout:#fitSpace.
+        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: topSpace-layout
 
-	|v p b1 b2 b3|
+        |v p b1 b2 b3|
 
-	v := StandardSystemView new.
-	p := VerticalPanelView in:v.
-	p verticalLayout:#topSpace.
-	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
+        v := StandardSystemView new.
+        p := VerticalPanelView in:v.
+        p verticalLayout:#topSpace.
+        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: bottom-layout
 
-	|v p b1 b2 b3|
+        |v p b1 b2 b3|
 
-	v := StandardSystemView new.
-	p := VerticalPanelView in:v.
-	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.
-	b3 := Button label:'button3' in:p.
-	v extent:100 @ 300.
-	v open
+        v := StandardSystemView new.
+        p := VerticalPanelView in:v.
+        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.
+        b3 := Button label:'button3' in:p.
+        v extent:100 @ 300.
+        v open
 
 
     example: bottomSpace-layout
 
-	|v p b1 b2 b3|
+        |v p b1 b2 b3|
 
-	v := StandardSystemView new.
-	p := VerticalPanelView in:v.
-	p verticalLayout:#bottomSpace.
-	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
+        v := StandardSystemView new.
+        p := VerticalPanelView in:v.
+        p verticalLayout:#bottomSpace.
+        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: spread-layout
 
-	|v p b1 b2 b3|
+        |v p b1 b2 b3|
 
-	v := StandardSystemView new.
-	p := VerticalPanelView in:v.
-	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
+        v := StandardSystemView new.
+        p := VerticalPanelView in:v.
+        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: spreadSpace-layout
 
-	|v p b1 b2 b3|
+        |v p b1 b2 b3|
 
-	v := StandardSystemView new.
-	p := VerticalPanelView in:v.
-	p verticalLayout:#spreadSpace.
-	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
+        v := StandardSystemView new.
+        p := VerticalPanelView in:v.
+        p verticalLayout:#spreadSpace.
+        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: fit-layout
 
-	|v p b1 b2 b3|
+        |v p b1 b2 b3|
 
-	v := StandardSystemView new.
-	p := VerticalPanelView in:v.
-	p verticalLayout:#fit.
-	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
+        v := StandardSystemView new.
+        p := VerticalPanelView in:v.
+        p verticalLayout:#fit.
+        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: fitSpace-layout
 
-	|v p b1 b2 b3|
+        |v p b1 b2 b3|
 
-	v := StandardSystemView new.
-	p := VerticalPanelView in:v.
-	p verticalLayout:#fitSpace.
-	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
+        v := StandardSystemView new.
+        p := VerticalPanelView in:v.
+        p verticalLayout:#fitSpace.
+        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: fully fitSpace
 
-	|v p b1 b2 b3|
+        |v p b1 b2 b3|
 
-	v := StandardSystemView new.
-	p := VerticalPanelView in:v.
-	p verticalLayout:#fitSpace.
-	p horizontalLayout:#fitSpace.
-	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
+        v := StandardSystemView new.
+        p := VerticalPanelView in:v.
+        p verticalLayout:#fitSpace.
+        p horizontalLayout:#fitSpace.
+        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 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
+        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 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
+        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
 
 
     example: a panel in a panel
 
-	|v hp p b1 b2 b3|
-
-	v := StandardSystemView new.
-
-	hp := HorizontalPanelView in:v.
-	hp verticalLayout:#fit.
-	hp horizontalLayout:#fitSpace.
-	hp origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).
+        |v hp p b1 b2 b3|
 
-	1 to:3 do:[:i |
-	    p := VerticalPanelView in:hp.
-	    p borderWidth:0.
-	    p verticalLayout:#fitSpace.
-	    p horizontalLayout:#fit.
-	    b1 := Button label:'button1' in:p.
-	    b2 := Button label:'button2' in:p.
-	    b3 := Button label:'button3' in:p.
-	].
-
-	v extent:300 @ 100.
-	v open
-"
-! !
-
-!VerticalPanelView methodsFor:'accessing'!
+        v := StandardSystemView new.
 
-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
-    ]
-!
+        hp := HorizontalPanelView in:v.
+        hp verticalLayout:#fit.
+        hp horizontalLayout:#fitSpace.
+        hp origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).
 
-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
-    ]
-!
+        1 to:3 do:[:i |
+            p := VerticalPanelView in:hp.
+            p borderWidth:0.
+            p verticalLayout:#fitSpace.
+            p horizontalLayout:#fit.
+            b1 := Button label:'button1' in:p.
+            b2 := Button label:'button2' in:p.
+            b3 := Button label:'button3' in:p.
+        ].
 
-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
-    "return a good extent, one that makes subviews fit"
-
-    |sumOfHeights maxWidth maxHeight|
+        v extent:300 @ 100.
+        v open
 
-    subViews isNil ifTrue:[^ horizontalSpace @ verticalSpace].
-
-    "compute net height needed"
-
-    sumOfHeights := 0.
-    maxWidth := 0.
-    maxHeight := 0.
+    example: checkToggles in a panel
 
-    subViews do:[:child |
-	|childsPreference|
+        |panel|
 
-	childsPreference := child preferedExtent.
-	sumOfHeights := sumOfHeights + childsPreference y.
-	maxHeight := maxHeight max:childsPreference y.
-	maxWidth := maxWidth max:childsPreference x.
+        panel := VerticalPanelView new.
+        panel horizontalLayout:#left.
 
-"/        sumOfHeights := sumOfHeights + child heightIncludingBorder.
-"/        maxWidth := maxWidth max:(child widthIncludingBorder).
-"/        maxHeight := maxHeight max:(child heightIncludingBorder).
-    ].
-    borderWidth ~~ 0 ifTrue:[
-	sumOfHeights := sumOfHeights + (horizontalSpace * 2).
-	maxWidth := maxWidth + (horizontalSpace * 2).
-    ].
-    (vLayout == #fit or:[vLayout == #fitSpace]) ifTrue:[
-	sumOfHeights := maxHeight * subViews size.
-	borderWidth ~~ 0 ifTrue:[
-	    sumOfHeights := sumOfHeights + (verticalSpace * 2).
-	]
-    ] ifFalse:[
-	sumOfHeights := sumOfHeights + ((subViews size - 1) * verticalSpace).
-    ].
+        panel add:((CheckBox on:true asValue) label:'this is toggle number 1'; resize).
+        panel add:((CheckBox on:false asValue) label:'nr 2 '; resize).
+        panel add:((CheckBox on:true asValue) label:'number 3 '; resize).
 
-    ((hLayout == #leftSpace) or:[hLayout == #rightSpace]) ifTrue:[
-	maxWidth := maxWidth + horizontalSpace
-    ] ifFalse:[
-	((hLayout == #fitSpace) or:[hLayout == #center]) ifTrue:[
-	    maxWidth := maxWidth + (horizontalSpace * 2)
-	]        
-    ].
-    ^ maxWidth @ sumOfHeights
+        panel extent:(panel preferedExtent).
+        panel open
+"
 ! !
 
 !VerticalPanelView methodsFor:'layout'!
@@ -583,7 +466,10 @@
      now set positions
     "
     subViews do:[:child |
-	|xpos|
+	|xpos bwChild wChild|
+
+	wChild := child widthIncludingBorder.
+	bwChild := child borderWidth.
 
 	hLayout == #left ifTrue:[
 	    xpos := 0
@@ -592,21 +478,21 @@
 		xpos := horizontalSpace
 	    ] ifFalse:[
 		hLayout == #right ifTrue:[
-		    xpos := width - child widthIncludingBorder
+		    xpos := width - wChild
 		] ifFalse:[
 		    hLayout == #rightSpace ifTrue:[
-			xpos := width - horizontalSpace - child widthIncludingBorder.
+			xpos := width - horizontalSpace - wChild.
 		    ] ifFalse:[
 			hLayout == #fitSpace ifTrue:[
 			    xpos := horizontalSpace.
-			    child width:(width - (horizontalSpace + child borderWidth * 2))
+			    child width:(width - (horizontalSpace +  bwChild * 2))
 			] ifFalse:[
 			    hLayout == #fit ifTrue:[
 				xpos := 0.
-				child width:(width - (child borderWidth * 2))
+				child width:(width - (bwChild  * 2))
 			    ] ifFalse:[
 			       "centered"
-				xpos := (width - child widthIncludingBorder) // 2.
+				xpos := (width - wChild) // 2.
 			    ]
 			]
 		    ]
@@ -618,7 +504,7 @@
 	(vLayout == #fit or:[vLayout == #fitSpace]) ifTrue:[
 	    child origin:(xpos @ ypos rounded)
 		  corner:(xpos + (child width))
-			 @ (ypos + hEach - (child borderWidth)) rounded.
+			 @ (ypos + hEach - bwChild) rounded.
 	    ypos := ypos + hEach + space
 	] ifFalse:[
 	    child origin:(xpos@ypos).
@@ -626,3 +512,136 @@
 	]
     ]
 ! !
+
+!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
+!
+
+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
+    "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
+!
+
+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:aSymbol
+    "leftover for historic reasons - do not use any more"
+
+    self verticalLayout:aSymbol
+!
+
+layout
+    "leftover for historic reasons - do not use any more"
+
+    self verticalLayout
+! !
+
+!VerticalPanelView methodsFor:'queries'!
+
+preferedExtent
+    "return a good extent, one that makes subviews fit"
+
+    |sumOfHeights maxWidth maxHeight|
+
+    subViews isNil ifTrue:[^ horizontalSpace @ verticalSpace].
+
+    "compute net height needed"
+
+    sumOfHeights := 0.
+    maxWidth := 0.
+    maxHeight := 0.
+
+    subViews do:[:child |
+        |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).
+        maxWidth := maxWidth + (horizontalSpace * 2).
+    ].
+    (vLayout == #fit or:[vLayout == #fitSpace]) ifTrue:[
+        sumOfHeights := maxHeight * subViews size.
+        borderWidth ~~ 0 ifTrue:[
+            sumOfHeights := sumOfHeights + (verticalSpace * 2).
+        ]
+    ] ifFalse:[
+        sumOfHeights := sumOfHeights + ((subViews size - 1) * verticalSpace).
+    ].
+
+    ((hLayout == #leftSpace) or:[hLayout == #rightSpace]) ifTrue:[
+        maxWidth := maxWidth + horizontalSpace
+    ] ifFalse:[
+        ((hLayout == #fitSpace) or:[hLayout == #center]) ifTrue:[
+            maxWidth := maxWidth + (horizontalSpace * 2)
+        ]        
+    ].
+    ^ maxWidth @ sumOfHeights
+! !
+