VariableVerticalPanel.st
changeset 105 3d064ba4a0cc
parent 99 abb8fe62848f
child 116 be0971c081e2
--- a/VariableVerticalPanel.st	Sat Mar 18 06:16:33 1995 +0100
+++ b/VariableVerticalPanel.st	Sat Mar 18 06:16:50 1995 +0100
@@ -10,15 +10,15 @@
  hereby transferred.
 "
 
-'From Smalltalk/X, Version:2.10.4 on 6-mar-1995 at 20:01:51'!
+'From Smalltalk/X, Version:2.10.5 on 14-mar-1995 at 11:10:57 am'!
 
 View subclass:#VariableVerticalPanel
-	 instanceVariableNames:'barHeight barWidth separatingLine
-		shadowForm lightForm showHandle handlePosition handleColor
-		handleStyle noColor trackLine redrawLocked'
+	 instanceVariableNames:'barHeight barWidth separatingLine shadowForm lightForm showHandle
+                handlePosition handleColor handleStyle noColor trackLine
+                redrawLocked'
 	 classVariableNames:'DefaultShowHandle DefaultHandleStyle DefaultHandlePosition
-		DefaultTrackingLine DefaultSeparatingLine DefaultHandleColor
-		DefaultCursor'
+                DefaultTrackingLine DefaultSeparatingLine DefaultHandleColor
+                DefaultCursor'
 	 poolDictionaries:''
 	 category:'Views-Layout'
 !
@@ -27,7 +27,7 @@
 COPYRIGHT (c) 1991 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libwidg/VariableVerticalPanel.st,v 1.14 1995-03-06 21:06:00 claus Exp $
+$Header: /cvs/stx/stx/libwidg/VariableVerticalPanel.st,v 1.15 1995-03-18 05:16:36 claus Exp $
 '!
 
 !VariableVerticalPanel class methodsFor:'documentation'!
@@ -48,7 +48,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libwidg/VariableVerticalPanel.st,v 1.14 1995-03-06 21:06:00 claus Exp $
+$Header: /cvs/stx/stx/libwidg/VariableVerticalPanel.st,v 1.15 1995-03-18 05:16:36 claus Exp $
 "
 !
 
@@ -117,12 +117,6 @@
 
 !VariableVerticalPanel class methodsFor:'defaults'!
 
-shadowFormOn:aDisplay
-    "use same handle as Scroller"
-
-    ^ Scroller handleShadowFormOn:aDisplay
-!
-
 updateStyleCache
     DefaultShowHandle := StyleSheet at:'variablePanelShowHandle' default:true.
     DefaultHandleStyle := StyleSheet at:'variablePanelHandleStyle'.
@@ -132,6 +126,12 @@
     DefaultHandleColor := StyleSheet colorAt:'variablePanelHandleColor' default:Black.
 !
 
+shadowFormOn:aDisplay
+    "use same handle as Scroller"
+
+    ^ Scroller handleShadowFormOn:aDisplay
+!
+
 lightFormOn:aDisplay
     "use same handle as Scroller"
 
@@ -140,26 +140,6 @@
 
 !VariableVerticalPanel methodsFor:'drawing'!
 
-redrawHandlesFrom:start to:stop
-    "redraw some handles"
-
-    subViews notNil ifTrue:[
-	showHandle ifTrue:[
-	    self handleOriginsFrom:start to:stop do:[:hPoint |
-		self drawHandleAtX:(hPoint x) y:(hPoint y)
-	    ].
-	]
-    ]
-!
-
-redraw
-    "redraw all of the handles"
-
-    redrawLocked ~~ true ifTrue:[
-	self redrawHandlesFrom:1 to:(subViews size)
-    ]
-!
-
 drawHandleAtX:hx y:hy
     "draw a single handle at hx/hy"
 
@@ -235,6 +215,18 @@
     ]
 !
 
+redrawHandlesFrom:start to:stop
+    "redraw some handles"
+
+    subViews notNil ifTrue:[
+	showHandle ifTrue:[
+	    self handleOriginsFrom:start to:stop do:[:hPoint |
+		self drawHandleAtX:(hPoint x) y:(hPoint y)
+	    ].
+	]
+    ]
+!
+
 lockRedraw
     redrawLocked := true
 !
@@ -243,6 +235,14 @@
     redrawLocked := false
 !
 
+redraw
+    "redraw all of the handles"
+
+    redrawLocked ~~ true ifTrue:[
+	self redrawHandlesFrom:1 to:(subViews size)
+    ]
+!
+
 invertHandleBarAtX:hx y:hy
     self noClipByChildren.
     self xoring:[
@@ -270,12 +270,6 @@
 
 !VariableVerticalPanel methodsFor:'accessing'!
 
-barHeight
-    "return the height of the separating bar"
-
-    ^ barHeight
-!
-
 barHeight:nPixel
     "set the height of the separating bar"
 
@@ -292,6 +286,12 @@
     ]
 !
 
+barHeight
+    "return the height of the separating bar"
+
+    ^ barHeight
+!
+
 add:aView
     "a view is added; make its size relative (if not already done)"
 
@@ -367,6 +367,11 @@
     ]
 !
 
+initialize
+    super initialize.
+    noColor := Color noColor.
+!
+
 initStyle
     |mm|
 
@@ -407,9 +412,10 @@
     ].
 !
 
-initialize
-    super initialize.
-    noColor := Color noColor.
+defaultControllerClass
+    ^ VariableVerticalPanelController
+
+
 !
 
 initCursor
@@ -432,54 +438,42 @@
 	].
 	DefaultCursor := cursor
     ]
-!
-
-defaultControllerClass
-    ^ VariableVerticalPanelController
-
-
 ! !
 
 !VariableVerticalPanel methodsFor:'private'!
 
-handleOriginsDo:aBlock
-    "evaluate the argument block for every handle-origin"
-
-    self handleOriginsFrom:1 to:(subViews size) do:aBlock
-!
-
 handleOriginsFrom:start to:stop do:aBlock
     "evaluate the argument block for some handle-origins"
 
     |x hw hDelta|
 
     subViews notNil ifTrue:[
-	shadowForm notNil ifTrue:[
-	    hw := shadowForm width
-	] ifFalse:[
-	    hw := barWidth
-	].
-	(handleStyle ~~ #normal and:[handleStyle ~~ #mswindows]) ifTrue:[
-	    hDelta := barWidth // 2.
-	] ifFalse:[
-	    hDelta := 0
-	].
-	(handlePosition == #left) ifTrue:[
-	    x := hDelta
-	] ifFalse:[
-	    (handlePosition == #right) ifTrue:[
-		x := width - (1 "2" * hw) - margin - hDelta.
-	    ] ifFalse:[
-		x := width - barWidth // 2
-	    ]
-	].
-	(start + 1) to:stop do:[:index |
-	    |view y|
+        shadowForm notNil ifTrue:[
+            hw := shadowForm width
+        ] ifFalse:[
+            hw := barWidth
+        ].
+        (handleStyle ~~ #normal and:[handleStyle ~~ #mswindows]) ifTrue:[
+            hDelta := barWidth // 2.
+        ] ifFalse:[
+            hDelta := 0
+        ].
+        (handlePosition == #left) ifTrue:[
+            x := hDelta
+        ] ifFalse:[
+            (handlePosition == #right) ifTrue:[
+                x := width - (1 "2" * hw) - margin - hDelta.
+            ] ifFalse:[
+                x := width - barWidth // 2
+            ]
+        ].
+        (start + 1) to:stop do:[:index |
+            |view y|
 
-	    view := subViews at:index.
-	    y := view origin y - barHeight + 1.
-	    aBlock value:(x @ y)
-	]
+            view := subViews at:index.
+            y := view top "origin y" - barHeight + 1.
+            aBlock value:(x @ y)
+        ]
     ]
 !
 
@@ -489,53 +483,72 @@
     |step nSubviews|
 
     subViews notNil ifTrue:[
-	(start <= stop) ifTrue:[
-	    step := 1
-	] ifFalse:[
-	    step := -1
-	].
-	nSubviews := subViews size.
-	start to:stop by:step do:[:index |
-	    |bw view o1 o2 relOrg relCorner newOrg newCorner|
+        (start <= stop) ifTrue:[
+            step := 1
+        ] ifFalse:[
+            step := -1
+        ].
+        nSubviews := subViews size.
+        start to:stop by:step do:[:index |
+            |bw view o1 o2 relOrg relCorner newOrg newCorner newExt|
 
-	    view := subViews at:index.
-	    bw := view borderWidth.
+            view := subViews at:index.
+            bw := view borderWidth.
 
-	    index == 1 ifTrue:[
-		o1 := 0.
-	    ] ifFalse:[
-		o1 := barHeight // 2 - bw
-	    ].
-	    index ==  nSubviews ifTrue:[
-		o2 := 0.
-	    ] ifFalse:[
-		o2 := barHeight // 2 - bw
-	    ].
+            index == 1 ifTrue:[
+                o1 := 0.
+            ] ifFalse:[
+                o1 := barHeight // 2 - bw
+            ].
+            index ==  nSubviews ifTrue:[
+                o2 := 0.
+            ] ifFalse:[
+                o2 := barHeight // 2 - bw
+            ].
 
-	    relCorner := view relativeCorner.
-	    relCorner isNil ifTrue:[
-		self error:'subview must have relative corner'
-	    ].
-	    newCorner := view cornerFromRelativeCorner.
-	    newCorner notNil ifTrue:[
-		newCorner y:(newCorner y - o2)
-	    ].
+"
+            relCorner := view relativeCorner.
+            relCorner isNil ifTrue:[
+                self error:'subview must have relative corner'
+            ].
+            newCorner := view cornerFromRelativeCorner.
+            newCorner notNil ifTrue:[
+                newCorner y:(newCorner y - o2)
+            ].
 
-	    relOrg := view relativeOrigin.
-	    relOrg isNil ifTrue:[
-		self error:'subview must have relative origin'
-	    ].
-	    newOrg := view originFromRelativeOrigin.
-	    newOrg notNil ifTrue:[
-		(index ~~ 1) ifTrue:[  
-		    newOrg y:(newOrg y + o1)
-		].
-	    ].
-	    view pixelOrigin:newOrg corner:newCorner
-	]
+            relOrg := view relativeOrigin.
+            relOrg isNil ifTrue:[
+                self error:'subview must have relative origin'
+            ].
+            newOrg := view originFromRelativeOrigin.
+            newOrg notNil ifTrue:[
+                (index ~~ 1) ifTrue:[  
+                    newOrg y:(newOrg y + o1)
+                ].
+            ].
+            view pixelOrigin:newOrg corner:newCorner
+"
+            newOrg := view computeOrigin.
+            newOrg notNil ifTrue:[
+                (index ~~ 1) ifTrue:[  
+                    newOrg y:(newOrg y + o1)
+                ].
+            ].
+            newExt := view computeExtent.
+            newExt notNil ifTrue:[
+                newExt y:(newExt y - o2 - o1)
+            ].
+            view pixelOrigin:newOrg extent:newExt.
+        ]
     ]
 !
 
+handleOriginsDo:aBlock
+    "evaluate the argument block for every handle-origin"
+
+    self handleOriginsFrom:1 to:(subViews size) do:aBlock
+!
+
 anyNonRelativeSubviews
     "return true, if any of my subviews has no relative origin/extent"
 
@@ -582,11 +595,12 @@
     "tell subviews if I change size"
 
     shown ifTrue:[
-	(how == #smaller) ifTrue:[
-	    self resizeSubviewsFrom:1 to:(subViews size)
-	] ifFalse:[
-	    self resizeSubviewsFrom:(subViews size) to:1
-	]
-    ]
+        (how == #smaller) ifTrue:[
+            self resizeSubviewsFrom:1 to:(subViews size)
+        ] ifFalse:[
+            self resizeSubviewsFrom:(subViews size) to:1
+        ]
+    ].
+    self changed:#sizeOfView with:how.
 ! !