VerticalPanelView.st
changeset 380 6eb402d01ae0
parent 341 7f5c67028a04
child 585 8f395aba0173
equal deleted inserted replaced
379:a0ada7891fe9 380:6eb402d01ae0
   638 !VerticalPanelView methodsFor:'layout'!
   638 !VerticalPanelView methodsFor:'layout'!
   639 
   639 
   640 setChildPositions
   640 setChildPositions
   641     "(re)compute position of every child"
   641     "(re)compute position of every child"
   642 
   642 
   643     |ypos space sumOfHeights numChilds l hEach hInside maxWidth resizeToMax hL|
   643     |ypos space sumOfHeights numChilds l hEach hInside maxWidth resizeToMax hL m2|
   644 
   644 
   645     subViews isNil ifTrue:[^ self].
   645     subViews isNil ifTrue:[^ self].
   646 
   646 
   647     space := verticalSpace.
   647     space := verticalSpace.
   648     numChilds := subViews size.
   648     numChilds := subViews size.
   649     hInside := height - (margin * 2) + (borderWidth*2) - subViews last borderWidth.
   649     m2 := margin * 2.
       
   650     hInside := height - m2 + (borderWidth*2) - subViews last borderWidth.
   650 
   651 
   651     vLayout == #fitSpace ifTrue:[
   652     vLayout == #fitSpace ifTrue:[
   652 	"
   653         "
   653 	 adjust childs extents and set origins.
   654          adjust childs extents and set origins.
   654 	 Be careful to avoid accumulation of rounding errors
   655          Be careful to avoid accumulation of rounding errors
   655 	"
   656         "
   656 	hEach := (hInside - (numChilds + 1 * space)) / numChilds.
   657         hEach := (hInside - (numChilds + 1 * space)) / numChilds.
   657 	ypos := space + margin - borderWidth.
   658         ypos := space + margin - borderWidth.
   658     ] ifFalse:[
   659     ] ifFalse:[
   659 	vLayout == #fit ifTrue:[
   660         vLayout == #fit ifTrue:[
   660 	    "
   661             "
   661 	     adjust childs extents and set origins.
   662              adjust childs extents and set origins.
   662 	     Be careful to avoid accumulation of rounding errors
   663              Be careful to avoid accumulation of rounding errors
   663 	    "
   664             "
   664 	    hEach := (hInside - (numChilds - 1 * space)) / numChilds.
   665             hEach := (hInside - (numChilds - 1 * space)) / numChilds.
   665 	    ypos := margin - borderWidth.
   666             ypos := margin - borderWidth.
   666 	] ifFalse:[
   667         ] ifFalse:[
   667 	    "
   668             "
   668 	     compute net height needed
   669              compute net height needed
   669 	    "
   670             "
   670 	    sumOfHeights := subViews inject:0 into:[:sumSoFar :child | sumSoFar + child heightIncludingBorder].
   671             sumOfHeights := subViews inject:0 into:[:sumSoFar :child | sumSoFar + child heightIncludingBorder].
   671 
   672 
   672 	    l := vLayout.
   673             l := vLayout.
   673 	    ((l == #center) and:[numChilds == 1]) ifTrue:[
   674             ((l == #center) and:[numChilds == 1]) ifTrue:[
   674 		l := #spread
   675                 l := #spread
   675 	    ].
   676             ].
   676 	    (l == #spread and:[numChilds == 1]) ifTrue:[
   677             (l == #spread and:[numChilds == 1]) ifTrue:[
   677 		l := #spreadSpace
   678                 l := #spreadSpace
   678 	    ].
   679             ].
   679 
   680 
   680 	    "
   681             "
   681 	     compute position of topmost subview and space between them;
   682              compute position of topmost subview and space between them;
   682 	     if they do hardly fit, leave no space between them 
   683              if they do hardly fit, leave no space between them 
   683 	    "
   684             "
   684 	    ((sumOfHeights >= (height - (margin * 2)))
   685             ((sumOfHeights >= (height - m2))
   685 	    and:[l ~~ #fixTopSpace and:[l ~~ #fixTop]])  ifTrue:[
   686             and:[l ~~ #fixTopSpace and:[l ~~ #fixTop]]) ifTrue:[
   686 		"
   687                 "
   687 		 if we have not enough space for all the elements, 
   688                  if we have not enough space for all the elements, 
   688 		 fill them tight, and show what can be shown (at least)
   689                  fill them tight, and show what can be shown (at least)
   689 		"
   690                 "
   690 		ypos := 0.
   691                 ypos := margin.
   691 		space := 0
   692                 space := 0
   692 	    ] ifFalse:[
   693             ] ifFalse:[
   693 		l == #fixTopSpace ifTrue:[
   694                 l == #fixTopSpace ifTrue:[
   694 		    l := #topSpace
   695                     l := #topSpace
   695 		] ifFalse:[
   696                 ] ifFalse:[
   696 		    l == #fixTop ifTrue:[
   697                     l == #fixTop ifTrue:[
   697 			l := #top 
   698                         l := #top 
   698 		    ]
   699                     ]
   699 		].
   700                 ].
   700 		((l == #bottom) or:[l == #bottomSpace]) ifTrue:[
   701                 ((l == #bottom) or:[l == #bottomSpace]) ifTrue:[
   701 		    ypos := height - (space * (numChilds - 1)) - sumOfHeights.
   702                     ypos := height - (space * (numChilds - 1)) - sumOfHeights.
   702 	"
   703         "
   703 		    borderWidth == 0 ifTrue:[
   704                     borderWidth == 0 ifTrue:[
   704 			ypos := ypos + space 
   705                         ypos := ypos + space 
   705 		    ].
   706                     ].
   706 	"           
   707         "           
   707 		    l == #bottomSpace ifTrue:[
   708                     l == #bottomSpace ifTrue:[
   708 			ypos >= space ifTrue:[
   709                         ypos >= space ifTrue:[
   709 			    ypos := ypos - space
   710                             ypos := ypos - space
   710 			]
   711                         ]
   711 		    ].
   712                     ].
   712 
   713 
   713 		    ypos < 0 ifTrue:[
   714                     ypos < 0 ifTrue:[
   714 			space := space min:(height - sumOfHeights) // (numChilds + 1).
   715                         space := space min:(height - sumOfHeights) // (numChilds + 1).
   715 			ypos := height - (space * numChilds) - sumOfHeights.
   716                         ypos := height - (space * numChilds) - sumOfHeights.
   716 		    ]
   717                     ]
   717 		] ifFalse: [
   718                 ] ifFalse: [
   718 		    (l == #spread) ifTrue:[
   719                     (l == #spread) ifTrue:[
   719 			space := (height - sumOfHeights) // (numChilds - 1).
   720                         space := (height - m2 - sumOfHeights) // (numChilds - 1).
   720 			ypos := 0.
   721                         ypos := margin.
   721 			(space == 0) ifTrue:[
   722                         (space == 0) ifTrue:[
   722 			    ypos := (height - sumOfHeights) // 2
   723                             ypos := (height - sumOfHeights) // 2
   723 			]
   724                         ]
   724 		    ] ifFalse: [
   725                     ] ifFalse: [
   725 		      (l == #spreadSpace) ifTrue:[
   726                       (l == #spreadSpace) ifTrue:[
   726 			space := (height - sumOfHeights) // (numChilds + 1).
   727                         space := (height - sumOfHeights) // (numChilds + 1).
   727 			ypos := space.
   728                         ypos := space.
   728 			(space == 0) ifTrue:[
   729                         (space == 0) ifTrue:[
   729 			    ypos := (height - sumOfHeights) // 2
   730                             ypos := (height - sumOfHeights) // 2
   730 			]
   731                         ]
   731 		      ] ifFalse: [
   732                       ] ifFalse: [
   732 			((l == #top)
   733                         ((l == #top)
   733 			or:[l == #topSpace
   734                         or:[l == #topSpace
   734 			or:[l == #topFit
   735                         or:[l == #topFit
   735 			or:[l == #topSpaceFit]]]) ifTrue:[
   736                         or:[l == #topSpaceFit]]]) ifTrue:[
   736 			    space := space min:(height - sumOfHeights) // (numChilds + 1).
   737                             space := space min:(height - sumOfHeights - m2) // (numChilds + 1).
   737 			    (vLayout == #fixTop or:[vLayout == #fixTopSpace]) ifTrue:[
   738                             (vLayout == #fixTop or:[vLayout == #fixTopSpace]) ifTrue:[
   738 				space := space max:verticalSpace.
   739                                 space := space max:verticalSpace.
   739 			    ] ifFalse:[
   740                             ] ifFalse:[
   740 				space := space max:0.
   741                                 space := space max:0.
   741 			    ].
   742                             ].
   742 			    (l == #topSpace 
   743                             (l == #topSpace 
   743 			    or:[l == #topSpaceFit]) ifTrue:[
   744                             or:[l == #topSpaceFit]) ifTrue:[
   744 				ypos := space.
   745                                 ypos := space.
   745 			    ] ifFalse:[
   746                             ] ifFalse:[
   746 				ypos := 0
   747                                 "/
   747 			    ]
   748                                 "/ if the very first view has a 0-level AND
   748 			] ifFalse:[
   749                                 "/ my level is non-zero, begin with margin
   749 			    "center"
   750                                 "/
   750 			    ypos := (height - (sumOfHeights
   751                                 (margin ~~ 0 and:[subViews first level == 0]) ifTrue:[
   751 						 + ((numChilds - 1) * space))) // 2.
   752                                     ypos := margin
   752 			    ypos < 0 ifTrue:[
   753                                 ] ifFalse:[
   753 				space := (height - sumOfHeights) // (numChilds + 1).
   754                                     ypos := 0
   754 				ypos := (height - (sumOfHeights
   755                                 ]
   755 					       + ((numChilds - 1) * space))) // 2.
   756                             ]
   756 			    ]
   757                         ] ifFalse:[
   757 			]
   758                             "center"
   758 		      ]
   759                             ypos := (height - (sumOfHeights
   759 		    ]
   760                                                  + ((numChilds - 1) * space))) // 2.
   760 		]
   761                             ypos < 0 ifTrue:[
   761 	    ].
   762                                 space := (height - sumOfHeights) // (numChilds + 1).
   762 	].
   763                                 ypos := (height - (sumOfHeights
       
   764                                                + ((numChilds - 1) * space))) // 2.
       
   765                             ]
       
   766                         ]
       
   767                       ]
       
   768                     ]
       
   769                 ]
       
   770             ].
       
   771         ].
   763     ].
   772     ].
   764 
   773 
   765     hL := hLayout.
   774     hL := hLayout.
   766     resizeToMax := false.
   775     resizeToMax := false.
   767     (hLayout endsWith:'Max') ifTrue:[
   776     (hLayout endsWith:'Max') ifTrue:[
   768 	resizeToMax := true.
   777         resizeToMax := true.
   769 	maxWidth := subViews inject:0 into:[:maxSoFar :child | maxSoFar max:child widthIncludingBorder].
   778         maxWidth := subViews inject:0 into:[:maxSoFar :child | maxSoFar max:child widthIncludingBorder].
   770 	hL == #centerMax ifTrue:[hL := #center].
   779         hL == #centerMax ifTrue:[hL := #center].
   771 	hL == #rightMax ifTrue:[hL := #right].
   780         hL == #rightMax ifTrue:[hL := #right].
   772 	hL == #rightSpaceMax ifTrue:[hL := #rightSpace].
   781         hL == #rightSpaceMax ifTrue:[hL := #rightSpace].
   773 	hL == #leftMax ifTrue:[hL := #left].
   782         hL == #leftMax ifTrue:[hL := #left].
   774 	hL == #leftSpaceMax ifTrue:[hL := #leftSpace].
   783         hL == #leftSpaceMax ifTrue:[hL := #leftSpace].
   775     ].
   784     ].
   776 
   785 
   777     "
   786     "
   778      now set positions
   787      now set positions
   779     "
   788     "
   780     subViews keysAndValuesDo:[:index :child |
   789     subViews keysAndValuesDo:[:index :child |
   781 	|xpos bwChild wChild|
   790         |xpos advance bwChild wChild newWChild|
   782 
   791 
   783 	wChild := child widthIncludingBorder.
   792         wChild := child widthIncludingBorder.
   784 	bwChild := child borderWidth.
   793         bwChild := child borderWidth.
   785 
   794 
   786 	resizeToMax ifTrue:[
   795         resizeToMax ifTrue:[
   787 	    child width:(wChild := maxWidth - (bwChild  * 2)).
   796             child width:(wChild := maxWidth - (bwChild  * 2)).
   788 	].
   797         ].
   789 
   798 
   790 	hL == #left ifTrue:[
   799         hL == #left ifTrue:[
   791 	    xpos := 0
   800             xpos := 0
   792 	] ifFalse:[
   801         ] ifFalse:[
   793 	    hL == #leftSpace ifTrue:[
   802             hL == #leftSpace ifTrue:[
   794 		xpos := horizontalSpace
   803                 xpos := horizontalSpace
   795 	    ] ifFalse:[
   804             ] ifFalse:[
   796 		hL == #right ifTrue:[
   805                 hL == #right ifTrue:[
   797 		    xpos := width - wChild
   806                     xpos := width - wChild
   798 		] ifFalse:[
   807                 ] ifFalse:[
   799 		    hL == #rightSpace ifTrue:[
   808                     hL == #rightSpace ifTrue:[
   800 			xpos := width - horizontalSpace - wChild.
   809                         xpos := width - horizontalSpace - wChild.
   801 		    ] ifFalse:[
   810                     ] ifFalse:[
   802 			hL == #fitSpace ifTrue:[
   811                         hL == #fitSpace ifTrue:[
   803 			    xpos := horizontalSpace.
   812                             xpos := horizontalSpace.
   804 			    child width:(width - (horizontalSpace +  bwChild * 2))
   813                             newWChild := width - (horizontalSpace +  bwChild * 2)
   805 			] ifFalse:[
   814                         ] ifFalse:[
   806 			    hL == #fit ifTrue:[
   815                             hL == #fit ifTrue:[
   807 				xpos := 0.
   816                                 newWChild := width - (bwChild * 2).
   808 				child width:(width - (bwChild  * 2))
   817                                 child level == 0 ifTrue:[
   809 			    ] ifFalse:[
   818                                     xpos := margin.
   810 				"centered"
   819                                     newWChild := newWChild - m2
   811 				 xpos := (width - wChild) // 2.
   820                                 ] ifFalse:[
   812 			    ]
   821                                     xpos := 0. 
   813 			]
   822                                 ].
   814 		    ]
   823                             ] ifFalse:[
   815 		]
   824                                 "centered"
   816 	    ]
   825                                  xpos := (width - m2 - wChild) // 2.
   817 	].
   826                             ]
   818 	(xpos < 0) ifTrue:[ xpos := 0 ].
   827                         ]
   819 
   828                     ]
   820 	(vLayout == #fit 
   829                 ]
   821 	or:[vLayout == #fitSpace]) ifTrue:[
   830             ]
   822 	    child origin:(xpos @ ypos rounded)
   831         ].
   823 		  corner:(xpos + (child width - 1))
   832         newWChild notNil ifTrue:[
   824 			 @ (ypos + hEach - bwChild - 1) rounded.
   833             child width:newWChild
   825 	    ypos := ypos + hEach + space
   834         ].
   826 	] ifFalse:[
   835 
   827 	    child origin:(xpos@ypos).
   836         (xpos < 0) ifTrue:[ xpos := 0 ].
   828 	    ypos := ypos + (child heightIncludingBorder) + space
   837 
   829 	].
   838         (vLayout == #fit 
   830 
   839         or:[vLayout == #fitSpace]) ifTrue:[
   831 	index == numChilds ifTrue:[
   840             child origin:(xpos @ ypos rounded)
   832 	    |y|
   841                   corner:(xpos + (child width - 1))
   833 
   842                          @ (ypos + hEach - bwChild - 1) rounded.
   834 	    vLayout == #topFit ifTrue:[
   843             advance := hEach
   835 		y := height - margin - 1.
   844         ] ifFalse:[
   836 	    ].
   845             child origin:(xpos@ypos).
   837 	    vLayout == #topSpaceFit ifTrue:[
   846             advance := child heightIncludingBorder
   838 		y := height - margin - 1 - space
   847         ].
   839 	    ].
   848         ypos := ypos + advance + space.
   840 	    y notNil ifTrue:[
   849 
   841 		subViews last corner:(xpos + child width - 1) @ y
   850         index == numChilds ifTrue:[
   842 	    ]
   851             |y|
   843 	]
   852 
       
   853             (vLayout == #topFit or:[vLayout == #topSpaceFit]) ifTrue:[
       
   854                 y := height - margin - 1.
       
   855                 vLayout == #topSpaceFit ifTrue:[
       
   856                     y := y - space
       
   857                 ].
       
   858             ].
       
   859             y notNil ifTrue:[
       
   860                 subViews last corner:(xpos + child width - 1) @ y
       
   861             ]
       
   862         ]
   844     ]
   863     ]
   845 
   864 
   846     "Modified: 4.9.1995 / 18:43:29 / claus"
   865     "Modified: 4.9.1995 / 18:43:29 / claus"
       
   866     "Modified: 22.2.1996 / 21:25:42 / cg"
   847 ! !
   867 ! !
   848 
   868 
   849 !VerticalPanelView methodsFor:'queries'!
   869 !VerticalPanelView methodsFor:'queries'!
   850 
   870 
   851 preferredExtent
   871 preferredExtent
   852     "return a good extent, one that makes subviews fit"
   872     "return a good extent, one that makes subviews fit"
   853 
   873 
   854     |sumOfHeights maxWidth maxHeight|
   874     |sumOfHeights maxWidth maxHeight m2|
   855 
   875 
   856     subViews isNil ifTrue:[^ horizontalSpace @ verticalSpace].
   876     subViews isNil ifTrue:[^ horizontalSpace @ verticalSpace].
   857 
   877 
   858     "compute net height needed"
   878     "compute net height needed"
   859 
   879 
   900     ] ifFalse:[
   920     ] ifFalse:[
   901         ((hLayout == #fitSpace) or:[hLayout == #center]) ifTrue:[
   921         ((hLayout == #fitSpace) or:[hLayout == #center]) ifTrue:[
   902             maxWidth := maxWidth + (horizontalSpace * 2)
   922             maxWidth := maxWidth + (horizontalSpace * 2)
   903         ]        
   923         ]        
   904     ].
   924     ].
   905     ^ maxWidth @ sumOfHeights
   925     m2 := margin * 2.
   906 
   926     ^ (maxWidth + m2) @ (sumOfHeights + m2)
   907     "Modified: 9.2.1996 / 18:56:07 / cg"
   927 
       
   928     "Modified: 22.2.1996 / 21:14:02 / cg"
   908 ! !
   929 ! !
   909 
   930 
   910 !VerticalPanelView class methodsFor:'documentation'!
   931 !VerticalPanelView class methodsFor:'documentation'!
   911 
   932 
   912 version
   933 version
   913     ^ '$Header: /cvs/stx/stx/libwidg/VerticalPanelView.st,v 1.19 1996-02-09 17:57:17 cg Exp $'
   934     ^ '$Header: /cvs/stx/stx/libwidg/VerticalPanelView.st,v 1.20 1996-02-22 20:27:08 cg Exp $'
   914 ! !
   935 ! !