HorizontalPanelView.st
author claus
Tue, 09 May 1995 03:57:16 +0200
changeset 125 3ffa271732f7
parent 118 3ee5ea99d0e2
child 127 462396b08e30
permissions -rw-r--r--
.

"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

PanelView subclass:#HorizontalPanelView
       instanceVariableNames:''
       classVariableNames:''
       poolDictionaries:''
       category:'Views-Layout'
!

HorizontalPanelView comment:'
COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libwidg/HorizontalPanelView.st,v 1.10 1995-05-09 01:55:48 claus Exp $
'!

!HorizontalPanelView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

version
"
$Header: /cvs/stx/stx/libwidg/HorizontalPanelView.st,v 1.10 1995-05-09 01:55:48 claus Exp $
"
!

documentation
"
    a View which arranges its child-views in a horizontal row.
    All real work is done in PanelView - only the layout computation is
    redefined here.

    The layout is controlled the instance variables: 
	horizontalLayout and verticalLayout
    in addition to horizontalSpace and verticalSpace.

    The horizontal layout can be any of:

	#left           arrange elements at the left
	#leftSpace      arrange elements at the left, start with spacing
	#fixLeft        same as #left, but do not reduce spacing in case of no fit
	#fixLeftSpace   same as #leftSpace, but do not reduce spacing in case of no fit
	#right          arrange elements at the right
	#rightSpace     arrange elements at the right, start with spacing
	#center         arrange elements in the center
	#spread         spread elements evenly
	#spreadSpace    spread elements evenly with spacing at the ends
	#fit            like spread, but resize elements for tight packing
	#fitSpace       like fit, with additional spacing at the far ends
	#leftFit        like left, but extend the last element to the right
	#leftSpaceFit   like leftSpace, but extend the last element to the right

    the vertical layout can be:

	#top            place element at the top
	#topSpace       place element at the top, offset by verticalSpace
	#center         place it horizontally centered
	#bottom         place it at the bottom
	#bottomSpace    place it at the bottom, offset by verticalSpace
	#fit            resize elements vertically to fit this panel
	#fitSpace       like fit, but with spacing

    The defaults is #center for both directions.
    The layout is changed by the messages #verticalLayout: and #horizontalLayout:.
    For backward compatibility (to times, where only hLayout existed), the simple
    #layout: does the same as #horizontalLayout:. Do not use this old method.

    By combining Horizontal- and VerticalPanels (i.e. place a hPanel into a
    vPanel), most layouts should be implementable.
    However, ff none of these layout/space combinations is exactly what you need 
    in your application, create a subclass, and redefine the setChildPositions 
    method there.

    TODO: for completeness, support #fixRight, #fixRightSpace,
	  #rightFit, #rightSpaceFit layouts
"
!

examples
"
    These examples show the effect of various horizontalLayout and
    verticalLayout settings. Try them all. Especially, notice the
    differences between the xxx and xxxSpace layouts and the effect of
    setting different values for the spacing.
    Try resizing the view and see how the elements get rearranged.

    Most of the examples below place 3 buttons onto a panel; Of course,
    you can put any other view into a panel ... the last examples show this.


    example: default layout (centered)

	|v p b1 b2 b3|

	v := StandardSystemView new.
	v label:'default: center'.

	p := HorizontalPanelView 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:300 @ 100.
	v open


    example: left-layout (vertical is default -> centered)

	|v p b1 b2 b3|

	v := StandardSystemView new.
	p := HorizontalPanelView in:v.
	v label:'hL=left; vL=default (center)'.

	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:300 @ 100.
	v open


    example: left starting with spacing (vertical is default -> centered)

	|v p b1 b2 b3|

	v := StandardSystemView new.
	p := HorizontalPanelView in:v.
	v label:'hL=leftSpace; vL=center'.

	p horizontalLayout:#leftSpace.
	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:300 @ 100.
	v open


    example: leftFit-layout (vertical is default -> centered)

	|v p b1 b2 b3|

	v := StandardSystemView new.
	p := HorizontalPanelView in:v.
	v label:'hL=leftFit; vL=center'.

	p horizontalLayout:#leftFit.
	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:300 @ 100.
	v open


    example: leftSpaceFit-layout (vertical is default -> centered)

	|v p b1 b2 b3|

	v := StandardSystemView new.
	p := HorizontalPanelView in:v.
	v label:'hL=leftSpaceFit; vL=center'.

	p horizontalLayout:#leftSpaceFit.
	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:300 @ 100.
	v open


    example: right-layout (vertical is default -> centered)

	|v p b1 b2 b3|

	v := StandardSystemView new.
	p := HorizontalPanelView in:v.
	v label:'hL=right; vL=center'.

	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:300 @ 100.
	v open


    example: right with initial spacing (vertical is default -> centered)

	|v p b1 b2 b3|

	v := StandardSystemView new.
	p := HorizontalPanelView in:v.
	v label:'hL=rightSpace; vL=center'.

	p horizontalLayout:#rightSpace.
	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:300 @ 100.
	v open


    example: fit-layout (vertical is default -> centered)

	|v p b1 b2 b3|

	v := StandardSystemView new.
	p := HorizontalPanelView in:v.
	p horizontalLayout:#fit.
	v label:'hL=fit; vL=center'.

	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:300 @ 100.
	v open


    example: full fit i.e. no spacing (vertical is default -> centered)

	|v p b1 b2 b3|

	v := StandardSystemView new.
	p := HorizontalPanelView in:v.
	p horizontalLayout:#fit.
	p horizontalSpace:0.
	v label:'hL=fit hS=0; vL=center'.

	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:300 @ 100.
	v open


    example: fit with spacing (vertical is default -> centered)

	|v p b1 b2 b3|

	v := StandardSystemView new.
	p := HorizontalPanelView in:v.
	v label:'hL=fitSpace; vL=center'.

	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:300 @ 100.
	v open


    example: spread-layout (vertical is default -> centered)

	|v p b1 b2 b3|

	v := StandardSystemView new.
	p := HorizontalPanelView in:v.
	p horizontalLayout:#spread.
	v label:'hL=spread; vL=center'.

	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:300 @ 100.
	v open


    example: spread with spacing (vertical is default -> centered)

	|v p b1 b2 b3|

	v := StandardSystemView new.
	p := HorizontalPanelView in:v.
	v label:'hL=spreadSpace; vL=center'.

	p horizontalLayout:#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:300 @ 100.
	v open


    example: spread with spacing; vertical fit

	|v p b1 b2 b3|

	v := StandardSystemView new.
	p := HorizontalPanelView in:v.
	v label:'hL=spreadSpace; vL=fit'.

	p horizontalLayout:#spreadSpace.
	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:300 @ 100.
	v open


    example: spread with spacing; vertical fit with spacing

	|v p b1 b2 b3|

	v := StandardSystemView new.
	p := HorizontalPanelView in:v.
	v label:'hL=spreadSpace; vL=fitSpace'.

	p horizontalLayout:#spreadSpace.
	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:300 @ 100.
	v open


    example: fit - top

	|v p b1 b2 b3|

	v := StandardSystemView new.
	p := HorizontalPanelView in:v.
	v label:'hL=fit; vL=top'.

	p horizontalLayout:#fit.
	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:300 @ 100.
	v open


    example: fit with initial spacing

	|v p b1 b2 b3|

	v := StandardSystemView new.
	p := HorizontalPanelView in:v.
	v label:'hL=fitSpace; vL=top'.

	p horizontalLayout:#fitSpace.
	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:300 @ 100.
	v open


    example: fit with initial spacing in both directions

	|v p b1 b2 b3|

	v := StandardSystemView new.
	p := HorizontalPanelView in:v.
	v label:'hL=fitSpace; vL=fitSpace'.

	p horizontalLayout:#fitSpace.
	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:300 @ 100.
	v open


    example: fit without spacing in both directions

	|v p b1 b2 b3|

	v := StandardSystemView new.
	p := HorizontalPanelView in:v.
	v label:'hL=fit hS=0; vL=fit'.

	p horizontalLayout:#fit.
	p verticalLayout:#fit.
	p horizontalSpace:0.
	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:300 @ 100.
	v open


    example: fit with initial spacing; top with spacing

	|v p b1 b2 b3|

	v := StandardSystemView new.
	p := HorizontalPanelView in:v.
	v label:'hL=fitSpace; vL=topSpace'.

	p horizontalLayout:#fitSpace.
	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:300 @ 100.
	v open


    example: fit - top without spacing

	|v p b1 b2 b3|

	v := StandardSystemView new.
	p := HorizontalPanelView in:v.
	v label:'hL=fit; vL=top'.

	p horizontalLayout:#fit.
	p verticalLayout:#top.
	p horizontalSpace:0.
	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:300 @ 100.
	v open


    example: fit - bottom with spacing and bottomSpace

	|v p b1 b2 b3|

	v := StandardSystemView new.
	p := HorizontalPanelView in:v.
	v label:'hL=fitSpace; vL=bottomSpace'.

	p horizontalLayout:#fitSpace.
	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:300 @ 100.
	v open


    example: fit no horizontal space - bottom with spacing and bottomSpace

	|v p b1 b2 b3|

	v := StandardSystemView new.
	p := HorizontalPanelView in:v.
	v label:'hL=fit; vL=bottomSpace'.

	p horizontalLayout:#fit.
	p verticalLayout:#bottomSpace.
	p horizontalSpace:0.
	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:300 @ 100.
	v open

    example: placing hPanels into a vPanel

	|v vP hP1 hP2 hP3 b1 b2 b3 b4 b5 b6 b7 b8 b9|

	v := StandardSystemView new.
	vP := VerticalPanelView in:v.
	vP origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).
	vP verticalLayout:#fit;
	   verticalSpace:0;
	   horizontalLayout:#fit.

	hP1 := HorizontalPanelView in:vP.
	hP1 horizontalLayout:#fitSpace;
	    verticalLayout:#center.
	b1 := Button label:'button1' in:hP1.
	b2 := Button label:'button2' in:hP1.
	b3 := Button label:'button3' in:hP1.

	hP2 := HorizontalPanelView in:vP.
	hP2 horizontalLayout:#fitSpace;
	    verticalLayout:#center.
	b4 := Button label:'button4' in:hP2.
	b5 := Button label:'button5' in:hP2.
	b6 := Button label:'button6' in:hP2.

	hP3 := HorizontalPanelView in:vP.
	hP3 horizontalLayout:#fitSpace;
	    verticalLayout:#center.
	b7 := Button label:'button7' in:hP3.
	b8 := Button label:'button8' in:hP3.
	b9 := Button label:'button9' in:hP3.

	v extent:300 @ 300.
	v open

    example: a browser like table, where the rightmost list
	     extends to the far right.

	|v p l1 l2 l3|

	v := StandardSystemView new.
	p := HorizontalPanelView in:v.
	v label:'hL=leftFit hS=0; vL=fit'.

	p horizontalLayout:#leftFit.
	p horizontalSpace:0.
	p verticalLayout:#fit.
	p origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).

	l1 := ScrollableView for:FileSelectionList in:p.
	l1 stayInDirectory:true.
	l1 ignoreParentDirectory:true.
	l1 directory:'/'.
	l1 action:[:selection | l2 directory:(l1 selectedPathname)].

	l2 := ScrollableView for:FileSelectionList in:p.
	l2 stayInDirectory:true.
	l2 directory:nil.
	l2 ignoreParentDirectory:true.
	l2 action:[:selection | l3 directory:(l2 selectedPathname)].

	l3 := ScrollableView for:FileSelectionList in:p.
	l3 directory:nil.
	l3 ignoreParentDirectory:false.
	v extent:400 @ 300.
	v open


    trouble example: self resizing elements may cause trouble

	|v p l1 l2 l3|

	v := StandardSystemView new.
	p := HorizontalPanelView origin:(0.0 @ 0.0) corner:(1.0 @ 1.0) in:v.

	l1 := (Label label:'one' in:p) level:-1.
	l2 := (Label label:'two' in:p) level:-1.
	l3 := (Label label:'three' in:p) level:-1.

	v extent:400 @ 300.
	v open.

	(Delay forSeconds:5) wait.

	l1 label:'oneone'.
	l2 label:'twotwo'.
	l3 label:'threethree'.


    fixed trouble example: tell the panel that this situation may happen

	|v p l1 l2 l3|

	v := StandardSystemView new.
	p := HorizontalPanelView origin:(0.0 @ 0.0) corner:(1.0 @ 1.0) in:v.
	p elementsChangeSize:true.

	l1 := (Label label:'one' in:p) level:-1.
	l2 := (Label label:'two' in:p) level:-1.
	l3 := (Label label:'three' in:p) level:-1.

	v extent:400 @ 300.
	v open.

	(Delay forSeconds:5) wait.

	l1 label:'oneone'.
	l2 label:'twotwo'.
	l3 label:'threethree'.
"
! !

!HorizontalPanelView methodsFor:'accessing'!

horizontalLayout
    "return the horizontal layout as symbol.
     the returned value is one of
	#left 
	#leftSpace 
	#leftFit 
	#leftSpaceFit 
	#center
	#spread
	#fit
	#right 
	#rightSpace 
      the default is #center
      See the class documentation for  the meanings.
    "

    ^ hLayout
!

verticalLayout
    "return the vertical layout as a symbol.
     the returned value is one of
	#top / #topSpace
	#center
	#bottom / #bottomSpace
	#fit
      the default is #center
      See the class documentation for  the meanings.
    "

    ^ vLayout
!

horizontalLayout:aSymbol
    "change the horizontal layout as symbol.
     The argument, aSymbol must be one of:
	#left / #leftSpace 
	#leftFit / #leftSpaceFit 
	#center
	#spread / spreadSpace
	#fit / fitSpace
	#right / #rightSpace 
      the default (if never changed) is #center.
      See the class documentation for  the meanings.
    "

    (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
	#center
	#bottom / #bottomSpace
	#fit 
      the default (if never changed) is #center
      See the class documentation for  the meanings.
    "

    (vLayout ~~ aSymbol) ifTrue:[
	vLayout := aSymbol.
	self layoutChanged
    ]
!

layout
    "leftover for historic reasons - do not use any more"

    self horizontalLayout
!

layout:aSymbol
    "leftover for historic reasons - do not use any more"

    self horizontalLayout:aSymbol
! !


!HorizontalPanelView methodsFor:'queries'!

preferedExtent
    "return a good extent, one that makes subviews fit"

    |sumOfWidths maxHeight maxWidth|

    subViews isNil ifTrue:[^ horizontalSpace @ verticalSpace].

    "compute net height needed"

    sumOfWidths := 0.
    maxHeight := 0.
    maxWidth := 0.

    subViews do:[:child |
	|childsPreference|

	childsPreference := child preferedExtent.
	sumOfWidths := sumOfWidths + childsPreference x.
	maxHeight := maxHeight max:childsPreference y.
	maxWidth := maxWidth max:childsPreference x.

"/        sumOfWidths := sumOfWidths + child widthIncludingBorder.
"/        maxHeight := maxHeight max:(child heightIncludingBorder).
"/        maxWidth := maxWidth max:(child widthIncludingBorder).
    ].
    borderWidth ~~ 0 ifTrue:[
	sumOfWidths := sumOfWidths + (horizontalSpace * 2).
	maxHeight := maxHeight + (verticalSpace * 2).
    ].
    (hLayout == #fit or:[hLayout == #fitSpace]) ifTrue:[
	sumOfWidths := maxWidth * subViews size.
	borderWidth ~~ 0 ifTrue:[
	    sumOfWidths := sumOfWidths + (verticalSpace * 2).
	]
    ] ifFalse:[
	sumOfWidths := sumOfWidths + ((subViews size - 1) * horizontalSpace).
    ].

    ((vLayout == #topSpace) or:[vLayout == #bottomSpace]) ifTrue:[
	maxHeight := maxHeight + verticalSpace
    ] ifFalse:[
	((vLayout == #fitSpace)  or:[vLayout == #center]) ifTrue:[
	    maxHeight := maxHeight + (verticalSpace * 2)
	]        
    ].

    ^ sumOfWidths @ maxHeight
! !

!HorizontalPanelView methodsFor:'layout'!

setChildPositions
    "(re)compute position of every child whenever childs are added or
     my size has changed"

    |xpos space sumOfWidths numChilds l wEach wInside hL vL|

    subViews isNil ifTrue:[^ self].

    space := horizontalSpace.
    numChilds := subViews size.
    wInside := width - (margin * 2) + (borderWidth*2) - subViews last borderWidth.

    hL := hLayout.
    vL := vLayout.

    hL == #fitSpace ifTrue:[
	"
	 adjust childs extents and set origins.
	 Be careful to avoid accumulation of rounding errors
	"
	wEach := (wInside - (numChilds + 1 * space)) / numChilds.
	xpos := space + margin - borderWidth.
    ] ifFalse:[
	hL == #fit ifTrue:[
	    "
	     adjust childs extents and set origins.
	     Be careful to avoid accumulation of rounding errors
	    "
	    wEach := (wInside - (numChilds - 1 * space)) / numChilds.
	    xpos := margin - borderWidth.
	] ifFalse:[
	    "
	     compute net width needed
	    "
	    sumOfWidths := subViews inject:0 into:[:sumSoFar :child | sumSoFar + child widthIncludingBorder].

	    l := hL.
	    ((l == #center) and:[numChilds == 1]) ifTrue:[
		l := #spread
	    ].
	    (l == #spread and:[numChilds == 1]) ifTrue:[
		l := #spreadSpace
	    ].

	    "
	     compute position of leftmost subview and space between them;
	     if they do hardly fit, leave no space between them 
	    "
	    ((sumOfWidths >= (width - (margin * 2))) 
	    and:[l ~~ #fixLeftSpace and:[l ~~ #fixLeft]]) ifTrue:[
		xpos := 0.
		space := 0
	    ] ifFalse: [
		l == #fixLeftSpace ifTrue:[
		    l := #leftSpace
		] ifFalse:[
		    l == #fixLeft ifTrue:[
			l := #left
		    ]
		].
		((l == #right) or:[l == #rightSpace]) ifTrue:[
		    xpos := width - (space * (numChilds - 1)) - sumOfWidths.
	"
		    borderWidth == 0 ifTrue:[
			xpos := xpos + space 
		    ].
	"
		    l == #rightSpace ifTrue:[
			xpos >= space ifTrue:[
			    xpos := xpos - space
			]
		    ].

		    xpos < 0 ifTrue:[
			space := space min:(width - sumOfWidths) // (numChilds + 1).
			xpos := width - (space * numChilds) - sumOfWidths.
		    ]
		] ifFalse:[
		    (l == #spread) ifTrue:[
			space := (width - sumOfWidths) // (numChilds - 1).
			xpos := 0.
			(space == 0) ifTrue:[
			    xpos := (width - sumOfWidths) // 2
			]
		    ] ifFalse:[
		      (l == #spreadSpace) ifTrue:[
			space := (width - sumOfWidths) // (numChilds + 1).
			xpos := space.
			(space == 0) ifTrue:[
			    xpos := (width - sumOfWidths) // 2
			]
		      ] ifFalse:[
			((l == #left) 
			or:[l == #leftSpace
			or:[l == #leftFit
			or:[l == #leftSpaceFit]]]) ifTrue:[
			    space := space min:(width - sumOfWidths) // (numChilds + 1).
			    (hL == #fixLeft or:[hL == #fixLeftSpace]) ifTrue:[
				space := space max:horizontalSpace.
			    ] ifFalse:[
				space := space max:0.
			    ].
			    (l == #leftSpace 
			    or:[l == #leftSpaceFit]) ifTrue:[
				xpos := space.
			    ] ifFalse:[
				xpos := 0
			    ]
	"
			    borderWidth == 0 ifTrue:[
				xpos := 0 
			    ].
	"
			] ifFalse:[
			    "center"
			    xpos := (width - (sumOfWidths
					      + ((numChilds - 1) * space))) // 2.
			    xpos < 0 ifTrue:[
				space := (width - sumOfWidths) // (numChilds + 1).
				xpos := (width - (sumOfWidths
					       + ((numChilds - 1) * space))) // 2.
			    ]
			]
		      ]
		    ]
		]
	    ].
	].
    ].

    "now set positions"

    subViews keysAndValuesDo:[:index :child |
	|ypos advance|

	vL == #top ifTrue:[
	    ypos := 0
	] ifFalse:[
	    vL == #topSpace ifTrue:[
		ypos := verticalSpace
	    ] ifFalse:[
		vL == #bottom ifTrue:[
		    ypos := height - child heightIncludingBorder
		] ifFalse:[
		    vL == #bottomSpace ifTrue:[
			ypos := height - verticalSpace - child heightIncludingBorder.
		    ] ifFalse:[
			vL == #fitSpace ifTrue:[
			    ypos := verticalSpace.
			    child height:(height - (verticalSpace + child borderWidth * 2))
			] ifFalse:[
			    vL == #fit ifTrue:[
				ypos := 0.
				child height:(height - (child borderWidth * 2))
			    ] ifFalse:[
				"centered"
				ypos := (height - child heightIncludingBorder) // 2.
			    ]
			]
		    ]
		]
	    ]
	].
	(ypos < 0) ifTrue:[ypos := 0].

	(hL == #fit or:[hL == #fitSpace]) ifTrue:[
	    child origin:(xpos truncated @ ypos)
		  corner:(xpos + wEach - (child borderWidth)) truncated
			 @ (ypos + child height).
	    advance := wEach.
	] ifFalse:[
	    child origin:(xpos @ ypos).
	    advance := child widthIncludingBorder
	].
	xpos := xpos + advance + space.

	index == numChilds ifTrue:[
	    |x|

	    hL == #leftFit ifTrue:[
		x := width - margin.
	    ].
	    hL == #leftSpaceFit ifTrue:[
		x := width - margin - space
	    ].
	    x notNil ifTrue:[
		subViews last corner:(x @ (ypos + child height))
	    ]
	]
    ].
! !