VariableVerticalPanel.st
changeset 59 450ce95a72a4
parent 38 4b9b70b2cc87
child 60 f3c738c24ce6
--- a/VariableVerticalPanel.st	Tue Aug 30 00:54:47 1994 +0200
+++ b/VariableVerticalPanel.st	Mon Oct 10 04:03:47 1994 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1991 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -11,22 +11,23 @@
 "
 
 View subclass:#VariableVerticalPanel
-         instanceVariableNames:'movedHandle prev start
-                                barHeight barWidth separatingLine
-                                shadowForm lightForm
-                                showHandle handlePosition 
-                                handleColor noColor
-                                trackLine'
-         classVariableNames:''
-         poolDictionaries:''
-         category:'Views-Layout'
+	 instanceVariableNames:'movedHandle prev start
+				barHeight barWidth separatingLine
+				shadowForm lightForm
+				showHandle handlePosition 
+				handleColor handleStyle noColor
+				trackLine'
+	 classVariableNames:'DefaultShowHandle DefaultHandleStyle DefaultHandlePosition
+			     DefaultTrackingLine DefaultSeparatingLine DefaultHandleColor'
+	 poolDictionaries:''
+	 category:'Views-Layout'
 !
 
 VariableVerticalPanel comment:'
 COPYRIGHT (c) 1991 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libwidg/VariableVerticalPanel.st,v 1.7 1994-08-07 13:23:37 claus Exp $
+$Header: /cvs/stx/stx/libwidg/VariableVerticalPanel.st,v 1.8 1994-10-10 03:03:22 claus Exp $
 '!
 
 !VariableVerticalPanel class methodsFor:'documentation'!
@@ -34,7 +35,7 @@
 copyright
 "
  COPYRIGHT (c) 1991 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -47,7 +48,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libwidg/VariableVerticalPanel.st,v 1.7 1994-08-07 13:23:37 claus Exp $
+$Header: /cvs/stx/stx/libwidg/VariableVerticalPanel.st,v 1.8 1994-10-10 03:03:22 claus Exp $
 "
 !
 
@@ -63,52 +64,52 @@
     The subvies dimensions MUST be given as relative sizes;
     typically creation is done as:
 
-        p := VariableVerticalPanel in:superView.
-        v1 := <someViewClass> origin:0.0 @ 0.0
-                              corner:1.0 @ 0.5
-                                  in:p.
-        v2 := <someViewClass> origin:0.0 @ 0.5 
-                              corner:1.0 @ 0.8 
-                                  in:p.
-        v3 := <someViewClass> origin:0.0 @ 0.8 
-                              corner:1.0 @ 1.0
-                                  in:p.
+	p := VariableVerticalPanel in:superView.
+	v1 := <someViewClass> origin:0.0 @ 0.0
+			      corner:1.0 @ 0.5
+				  in:p.
+	v2 := <someViewClass> origin:0.0 @ 0.5 
+			      corner:1.0 @ 0.8 
+				  in:p.
+	v3 := <someViewClass> origin:0.0 @ 0.8 
+			      corner:1.0 @ 1.0
+				  in:p.
 
    example:
-        |top p v1 v2 v3|
+	|top p v1 v2 v3|
 
-        top := StandardSystemView new.
-        top extent:300@300.
+	top := StandardSystemView new.
+	top extent:300@300.
 
-        p := VariableVerticalPanel 
-                 origin:0.0 @ 0.0
-                 corner:1.0 @ 1.0
-                 in:top.
-        v1 := ScrollableView for:SelectionInListView in:p.
-        v1 origin:0.0 @ 0.0
-           corner:1.0 @ 0.5.
-        v1 list:(FileDirectory directoryNamed:'/etc') contents.
-        v1 action:[:selNr |
-                |fullName stream text|
-                fullName := '/etc/' , v1 selectionValue.
-                stream := fullName asFilename readStream.
-                stream notNil ifTrue:[
-                    text := stream contents.
-                    v2 contents:text.
-                    v3 contents:text
-                ]
-        ].
+	p := VariableVerticalPanel 
+		 origin:0.0 @ 0.0
+		 corner:1.0 @ 1.0
+		 in:top.
+	v1 := ScrollableView for:SelectionInListView in:p.
+	v1 origin:0.0 @ 0.0
+	   corner:1.0 @ 0.5.
+	v1 list:(FileDirectory directoryNamed:'/etc') contents.
+	v1 action:[:selNr |
+		|fullName stream text|
+		fullName := '/etc/' , v1 selectionValue.
+		stream := fullName asFilename readStream.
+		stream notNil ifTrue:[
+		    text := stream contents.
+		    v2 contents:text.
+		    v3 contents:text
+		]
+	].
 
-        v2 := TextView 
-                 origin:0.0 @ 0.5 
-                 corner:1.0 @ 0.8 
-                 in:p.
-        v3 := ScrollableView 
-                 for:EditTextView 
-                 in:p.
-        v3 origin:0.0 @ 0.8 
-           corner:1.0 @ 1.0.
-        top open
+	v2 := TextView 
+		 origin:0.0 @ 0.5 
+		 corner:1.0 @ 0.8 
+		 in:p.
+	v3 := ScrollableView 
+		 for:EditTextView 
+		 in:p.
+	v3 origin:0.0 @ 0.8 
+	   corner:1.0 @ 1.0.
+	top open
 "
 ! !
 
@@ -124,6 +125,15 @@
     "use same handle as Scroller"
 
     ^ Scroller handleLightFormOn:aDisplay
+!
+
+updateStyleCache
+    DefaultShowHandle := StyleSheet at:'variablePanelShowHandle' default:true.
+    DefaultHandleStyle := StyleSheet at:'variablePanelHandleStyle'.
+    DefaultHandlePosition := StyleSheet at:'variablePanelHandlePosition' default:#right.
+    DefaultTrackingLine := StyleSheet at:'variablePanelTrackingLine' default:false.
+    DefaultSeparatingLine := StyleSheet at:'variablePanelSeparatingLine' default:false.
+    DefaultHandleColor := StyleSheet at:'variablePanelHandleColor' default:Black.
 ! !
 
 !VariableVerticalPanel methodsFor:'initializing'!
@@ -131,55 +141,59 @@
 initialize
     super initialize.
     noColor := Color noColor.
-    handleColor := Black.
 !
 
 initStyle
+    |mm|
+
     super initStyle.
 
-    showHandle := style ~~ #mswindows.
+    handleColor := DefaultHandleColor on:device.
+
+    showHandle := DefaultShowHandle.
 
-    (style == #next) ifTrue:[
-        shadowForm := self class shadowFormOn:device.
-        lightForm := self class lightFormOn:device.
-        self barHeight:(shadowForm height + 2).
-        barWidth := shadowForm width.
-        handlePosition := #center.
+    DefaultHandleStyle isNil ifTrue:[
+	handleStyle := style
     ] ifFalse:[
-        shadowForm := lightForm := nil.
-        handlePosition := #right
+	handleStyle := DefaultHandleStyle
+    ].
+    handleStyle == #next ifTrue:[
+	shadowForm := self class shadowFormOn:device.
+	lightForm := self class lightFormOn:device.
+
+	self barHeight:(shadowForm height + 2).
+	barWidth := shadowForm width.
+    ] ifFalse:[
+	shadowForm := lightForm := nil.
     ].
 
-    style == #motif ifTrue:[
-        trackLine := true.
-        separatingLine := "true" false. "its so ugly"
+    handlePosition := DefaultHandlePosition.
+    trackLine := DefaultTrackingLine.
+    separatingLine := DefaultSeparatingLine.
+
+    mm := device verticalPixelPerMillimeter.
+    self is3D ifTrue:[
+	self barHeight:(3 * mm) rounded
     ] ifFalse:[
-        trackLine := false.
-        separatingLine := false
+	self barHeight:(2 * mm) rounded
     ].
-
-    self is3D ifTrue:[
-        self barHeight:(3 * ViewSpacing)
-    ] ifFalse:[
-        self barHeight:(2 * ViewSpacing)
-    ].
-    barWidth := 2 * ViewSpacing. "motif style width"
+    barWidth := (2 * mm) rounded. "motif style width"
 !
 
 initCursor
     "set the cursor - a double arrow"
 
     cursor := Cursor sourceForm:(Form fromFile:'VVPanel.xbm')
-                     maskForm:(Form fromFile:'VVPanel_m.xbm')
-                     hotX:8
-                     hotY:8.
+		     maskForm:(Form fromFile:'VVPanel_m.xbm')
+		     hotX:8
+		     hotY:8.
     "
      if bitmaps are not available, use a standard cursor
     "
     cursor isNil ifTrue:[
-        "which one looks better ?"
-        cursor := Cursor upDownArrow
-        "cursor := Cursor upLimitArrow"
+	"which one looks better ?"
+	cursor := Cursor upDownArrow
+	"cursor := Cursor upLimitArrow"
     ]
 !
 
@@ -190,10 +204,10 @@
 
 fixSize 
     extentChanged ifTrue:[
-        super fixSize.
-        self resizeSubviewsFrom:1 to:(subViews size)
+	super fixSize.
+	self resizeSubviewsFrom:1 to:(subViews size)
     ] ifFalse:[
-        super fixSize
+	super fixSize
     ]
 ! !
 
@@ -206,9 +220,9 @@
 
     super add:aView.
     shown ifTrue:[
-        (superView isNil or:[superView shown]) ifTrue:[
-            self setupSubviewSizes
-        ]
+	(superView isNil or:[superView shown]) ifTrue:[
+	    self setupSubviewSizes
+	]
     ]
 !
 
@@ -217,9 +231,9 @@
 
     super removeSubView:aView.
     shown ifTrue:[
-        (superView isNil or:[superView shown]) ifTrue:[
-            self setupSubviewSizes
-        ]
+	(superView isNil or:[superView shown]) ifTrue:[
+	    self setupSubviewSizes
+	]
     ]
 !
 
@@ -230,12 +244,12 @@
 
     "if screen is very low-res, make certain bar is visible and catchable"
     (barHeight < 4) ifTrue:[
-        barHeight := 4
+	barHeight := 4
     ].
 
     "make it even so spacing is equally spreadable among subviews"
     barHeight odd ifTrue:[
-        barHeight := barHeight + 1
+	barHeight := barHeight + 1
     ]
 !
 
@@ -257,108 +271,101 @@
      styleSymbol may be #motif to draw a little knob or
      enything else to draw scrollBars handleForm"
 
-    (styleSymbol ~~ style) ifTrue:[
-        style := styleSymbol.
-        style == #next ifTrue:[
-            shadowForm := self class shadowFormOn:device.
-            lightForm := self class lightFormOn:device.
-        ] ifFalse:[
-            shadowForm := lightForm := nil
-        ].
+    (styleSymbol ~~ handleStyle) ifTrue:[
+	handleStyle := styleSymbol.
+	handleStyle == #next ifTrue:[
+	    shadowForm := self class shadowFormOn:device.
+	    lightForm := self class lightFormOn:device.
+	] ifFalse:[
+	    shadowForm := lightForm := nil
+	].
 
-        shadowForm notNil ifTrue:[
-            (self is3D and:[style ~~ #motif]) ifTrue:[
-                self barHeight:(shadowForm height + 2).
-                barWidth := shadowForm width
-            ]
-        ].
-        shown ifTrue:[
-            self resizeSubviewsFrom:1 to:(subViews size).
-            self redraw
-        ]
+	shadowForm notNil ifTrue:[
+	    (self is3D and:[handleStyle ~~ #motif]) ifTrue:[
+		self barHeight:(shadowForm height + 2).
+		barWidth := shadowForm width
+	    ]
+	].
+	shown ifTrue:[
+	    self resizeSubviewsFrom:1 to:(subViews size).
+	    self redraw
+	]
     ]
 ! !
 
 !VariableVerticalPanel methodsFor:'drawing'!
 
 drawHandleFormAtX:hx y:hy
-    "kludge for now"
-    (viewBackground colorId notNil
-     and:[shadowColor colorId notNil
-          and:[lightColor colorId notNil]]) ifTrue:[
-        self foreground:viewBackground background:noColor function:#xor.
-        self displayOpaqueForm:shadowForm x:hx y:hy.
-        self foreground:shadowColor function:#or.
-        self displayOpaqueForm:shadowForm x:hx y:hy.
-        self foreground:viewBackground function:#xor.
-        self displayOpaqueForm:lightForm x:hx y:hy.
-        self foreground:lightColor function:#or.
-        self displayOpaqueForm:lightForm x:hx y:hy.
-
-        self foreground:viewBackground.
-        paint := nil. "kludge to force paint to be really set"
-        self paint:viewBackground.
-        self function:#copy
-    ]
+    self paint:shadowColor.
+    self displayForm:shadowForm x:hx y:hy.
+    self paint:lightColor.
+    self displayForm:lightForm x:hx y:hy.
+    self paint viewBackground
 !
 
 drawHandleAtX:hx y:hy
     |h y m|
 
-    (self is3D and:[shadowForm notNil]) ifTrue:[
-        h := shadowForm height
+    shadowForm notNil ifTrue:[
+	h := shadowForm height
     ] ifFalse:[
-        h := barHeight - 4
+	h := barHeight - 4
     ].
 
     self paint:viewBackground.
     self fillRectangleX:margin y:hy 
-                  width:(width - margin - margin) 
-                  height:barHeight.
+		  width:(width - margin - margin) 
+		  height:barHeight.
 
-    self is3D ifTrue:[
-        m := (barHeight - h) // 2.
-        shadowForm isNil ifTrue:[
-            y := hy + (barHeight // 2).
-            separatingLine ifTrue:[
-                self paint:shadowColor.
-                self displayLineFromX:margin y:y toX:(width - margin) y:y.
-                y := y + 1.
-                self paint:lightColor.
-                self displayLineFromX:margin y:y toX:(width - margin) y:y.
-            ].
-            self paint:viewBackground.
-            self fillRectangleX:(hx - barWidth) y:hy 
-                         width:(barWidth + barWidth) 
-                         height:h.
+    (handleStyle ~~ #normal and:[handleStyle ~~ #mswindows]) ifTrue:[
+	m := (barHeight - h) // 2.
+	shadowForm isNil ifTrue:[
+	    y := hy + (barHeight // 2).
+	    separatingLine ifTrue:[
+		self paint:shadowColor.
+		self displayLineFromX:margin y:y toX:(width - margin) y:y.
+		y := y + 1.
+		self paint:lightColor.
+		self displayLineFromX:margin y:y toX:(width - margin) y:y.
+	    ].
+	    self paint:viewBackground.
+	    self fillRectangleX:(hx - barWidth) y:hy 
+			 width:(barWidth + barWidth) 
+			 height:h.
 
-            "/ y := hy.   "old"
-            y := hy - 1.  "2.10.3"
-            self drawEdgesForX:(hx - barWidth)
-                             y:(y + m)
-                         width:(barWidth + barWidth)
-                        height:h level:2
-        ] ifFalse:[
-            "/ y := hy.   "old"
-            y := hy - 1.  "2.10.3"
-            self drawHandleFormAtX:hx y:(y + m)
-        ].
-        style == #st80 ifTrue:[
-            y := hy - 1.
-            self paint:lightColor.
-            self displayLineFromX:margin y:y toX:(width - margin) y:y.
-            y := hy + barHeight - 2.
-            self paint:shadowColor.
-            self displayLineFromX:margin y:y toX:(width - margin) y:y.
-        ].
+	    y := hy.   
+	    handleStyle == #st80 ifTrue:[
+		y := y - 1
+	    ].
+	    self drawEdgesForX:(hx - barWidth)
+			     y:(y + m)
+			 width:(barWidth + barWidth)
+			height:h 
+			 level:2
+	] ifFalse:[
+	    y := hy.
+	    self drawHandleFormAtX:hx y:(y + m)
+	].
+	handleStyle == #st80 ifTrue:[
+	    y := hy - 1.
+	    self paint:lightColor.
+	    self displayLineFromX:margin y:y toX:(width - margin - margin - 1) y:y.
+	    self displayLineFromX:0 y:hy toX:0 y:(hy + barHeight - 1).
+	    y := hy + barHeight - 2.
+	    self paint:shadowColor.
+	    self displayLineFromX:margin y:y toX:(width - margin) y:y.
+		"uncomment the -1 if you dont like the notch at the right end"
+		"                            VVV"
+	    self displayLineFromX:width-1 y:hy" "-1" " toX:width-1 y:(hy + barHeight - 1).
+	].
     ] ifFalse:[
-        y := hy + barHeight - 1.
-        self paint:handleColor.
-        separatingLine ifTrue:[
-            self displayLineFromX:0 y:hy+1 toX:width y:hy+1.
-            self displayLineFromX:0 y:y toX:width y:y.
-        ].
-        self fillRectangleX:hx y:hy width:barHeight height:barHeight
+	y := hy + barHeight - 1.
+	self paint:handleColor.
+	separatingLine ifTrue:[
+	    self displayLineFromX:0 y:hy+1 toX:width y:hy+1.
+	    self displayLineFromX:0 y:y toX:width y:y.
+	].
+	self fillRectangleX:hx y:hy width:barHeight height:barHeight
     ]
 !
 
@@ -366,23 +373,23 @@
     "redraw some handles"
 
     subViews notNil ifTrue:[
-        showHandle ifTrue:[
-            self handleOriginsFrom:start to:stop do:[:hPoint |
-                self drawHandleAtX:(hPoint x) y:(hPoint y)
-            ].
-            movedHandle notNil ifTrue:[
-                self noClipByChildren.
-                self xoring:[
-                    trackLine ifTrue:[
-                        self displayLineFromX:0 y:prev+(barHeight // 2)
-                                          toX:width y:prev+(barHeight // 2).
-                    ] ifFalse:[
-                        self fillRectangleX:0 y:prev width:width height:barHeight
-                    ]
-                ].
-                self clipByChildren
-            ]
-        ]
+	showHandle ifTrue:[
+	    self handleOriginsFrom:start to:stop do:[:hPoint |
+		self drawHandleAtX:(hPoint x) y:(hPoint y)
+	    ].
+	    movedHandle notNil ifTrue:[
+		self noClipByChildren.
+		self xoring:[
+		    trackLine ifTrue:[
+			self displayLineFromX:0 y:prev+(barHeight // 2)
+					  toX:width y:prev+(barHeight // 2).
+		    ] ifFalse:[
+			self fillRectangleX:0 y:prev width:width height:barHeight
+		    ]
+		].
+		self clipByChildren
+	    ]
+	]
     ]
 !
 
@@ -398,11 +405,11 @@
     "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
+	]
     ]
 !
 
@@ -412,32 +419,32 @@
     |handle|
 
     ((button == 1) or:[button == #select]) ifTrue:[
-        handle := 1.
-        self handleOriginsDo:[:hPoint |
-            |hy|
+	handle := 1.
+	self handleOriginsDo:[:hPoint |
+	    |hy|
 
-            hy := hPoint y.
-            (by between:hy and:(hy + barHeight)) ifTrue:[
-                movedHandle := handle.
-                prev := hy.
-                start := by - hy.
-                self noClipByChildren.
-                self xoring:[
-                    trackLine ifTrue:[
-                        self displayLineFromX:0 y:hy+(barHeight // 2) 
-                                          toX:width y:hy+(barHeight // 2).
-                    ] ifFalse:[
-                        self fillRectangleX:0 y:hy width:width height:barHeight
-                    ]
-                ].
-                self clipByChildren.
-                ^ self
-            ].
-            handle := handle + 1
-        ].
-        movedHandle := nil
+	    hy := hPoint y.
+	    (by between:hy and:(hy + barHeight)) ifTrue:[
+		movedHandle := handle.
+		prev := hy.
+		start := by - hy.
+		self noClipByChildren.
+		self xoring:[
+		    trackLine ifTrue:[
+			self displayLineFromX:0 y:hy+(barHeight // 2) 
+					  toX:width y:hy+(barHeight // 2).
+		    ] ifFalse:[
+			self fillRectangleX:0 y:hy width:width height:barHeight
+		    ]
+		].
+		self clipByChildren.
+		^ self
+	    ].
+	    handle := handle + 1
+	].
+	movedHandle := nil
     ] ifFalse:[
-        super buttonPress:button x:bx y:by
+	super buttonPress:button x:bx y:by
     ]
 !
 
@@ -459,31 +466,31 @@
     limitTop := barHeight // 2.
     limitBot := self height - barHeight.
     movedHandle > 1 ifTrue:[
-        limitTop := (subViews at:movedHandle) origin y + (barHeight // 2)
+	limitTop := (subViews at:movedHandle) origin y + (barHeight // 2)
     ].
     movedHandle < (subViews size - 1) ifTrue:[
-        limitBot := (subViews at:(movedHandle + 2)) origin y - barHeight
+	limitBot := (subViews at:(movedHandle + 2)) origin y - barHeight
     ].
     limitBot := limitBot - barHeight.
     (ypos < limitTop) ifTrue:[ "check against view limits"
-        ypos := limitTop
+	ypos := limitTop
     ] ifFalse:[
-        (ypos > limitBot) ifTrue:[
-            ypos := limitBot
-        ]
+	(ypos > limitBot) ifTrue:[
+	    ypos := limitBot
+	]
     ].
 
     self noClipByChildren.
     self xoring:[
-        trackLine ifTrue:[
-            self displayLineFromX:0 y:prev+(barHeight // 2) 
-                              toX:width y:prev+(barHeight // 2).
-            self displayLineFromX:0 y:ypos+(barHeight // 2) 
-                              toX:width y:ypos+(barHeight // 2).
-        ] ifFalse:[
-            self fillRectangleX:0 y:prev width:width height:barHeight.
-            self fillRectangleX:0 y:ypos width:width height:barHeight
-        ]
+	trackLine ifTrue:[
+	    self displayLineFromX:0 y:prev+(barHeight // 2) 
+			      toX:width y:prev+(barHeight // 2).
+	    self displayLineFromX:0 y:ypos+(barHeight // 2) 
+			      toX:width y:ypos+(barHeight // 2).
+	] ifFalse:[
+	    self fillRectangleX:0 y:prev width:width height:barHeight.
+	    self fillRectangleX:0 y:ypos width:width height:barHeight
+	]
     ].
     self clipByChildren.
     prev := ypos
@@ -495,38 +502,38 @@
     |aboveView belowView aboveIndex belowIndex newY|
 
     ((button == 1) or:[button == #select]) ifTrue:[
-        movedHandle isNil ifTrue:[^ self].
+	movedHandle isNil ifTrue:[^ self].
 
-        "undo the last xor"
+	"undo the last xor"
 
-        self noClipByChildren.
-        self xoring:[
-            trackLine ifTrue:[
-                self displayLineFromX:0 y:prev+(barHeight // 2) 
-                                  toX:width y:prev+(barHeight // 2).
-            ] ifFalse:[
-                self fillRectangleX:0 y:prev width:width height:barHeight
-            ].
-        ].
-        self clipByChildren.
+	self noClipByChildren.
+	self xoring:[
+	    trackLine ifTrue:[
+		self displayLineFromX:0 y:prev+(barHeight // 2) 
+				  toX:width y:prev+(barHeight // 2).
+	    ] ifFalse:[
+		self fillRectangleX:0 y:prev width:width height:barHeight
+	    ].
+	].
+	self clipByChildren.
 
-        "compute the new relative heights"
+	"compute the new relative heights"
 
-        aboveIndex := movedHandle.
-        belowIndex := movedHandle + 1.
-        aboveView := subViews at:aboveIndex.
-        belowView := subViews at:belowIndex.
+	aboveIndex := movedHandle.
+	belowIndex := movedHandle + 1.
+	aboveView := subViews at:aboveIndex.
+	belowView := subViews at:belowIndex.
 
-        newY := (prev + start / height) asFloat.
-        aboveView relativeCorner:aboveView relativeCorner x @ newY.
-        belowView relativeOrigin:belowView relativeOrigin x @ newY.
-        self resizeSubviewsFrom:aboveIndex to:belowIndex.
+	newY := (prev + start / height) asFloat.
+	aboveView relativeCorner:aboveView relativeCorner x @ newY.
+	belowView relativeOrigin:belowView relativeOrigin x @ newY.
+	self resizeSubviewsFrom:aboveIndex to:belowIndex.
 
-        movedHandle := nil.
+	movedHandle := nil.
 
-        self redrawHandlesFrom:aboveIndex to:belowIndex
+	self redrawHandlesFrom:aboveIndex to:belowIndex
     ] ifFalse:[
-        super buttonRelease:button x:x y:y
+	super buttonRelease:button x:x y:y
     ]
 ! !
 
@@ -536,11 +543,11 @@
     "return true, if any of my subviews has no relative origin/extent"
 
     1 to:(subViews size) do:[:index |
-        |view|
+	|view|
 
-        view := subViews at:index.
-        view relativeExtent isNil ifTrue:[^ true].
-        view relativeOrigin isNil ifTrue:[^ true]
+	view := subViews at:index.
+	view relativeExtent isNil ifTrue:[^ true].
+	view relativeOrigin isNil ifTrue:[^ true]
     ].
     ^ false
 !
@@ -551,24 +558,24 @@
     |y h|
 
     self anyNonRelativeSubviews ifTrue:[
-        "there is at least one subview without
-         relative origin/extent - setup all subviews
-         to spread evenly ..."
+	"there is at least one subview without
+	 relative origin/extent - setup all subviews
+	 to spread evenly ..."
 
-        y := 0.0.
-        h := 1.0 / (subViews size).
+	y := 0.0.
+	h := 1.0 / (subViews size).
 
-        1 to:(subViews size) do:[:index |
-            |view|
+	1 to:(subViews size) do:[:index |
+	    |view|
 
-            view := subViews at:index.
-            index == subViews size ifTrue:[
-                view origin:(0.0 @ y) corner:(1.0 @ 1.0)
-            ] ifFalse:[
-                view origin:(0.0 @ y) corner:(1.0 @ (y + h))
-            ].
-            y := y + h
-        ]
+	    view := subViews at:index.
+	    index == subViews size ifTrue:[
+		view origin:(0.0 @ y) corner:(1.0 @ 1.0)
+	    ] ifFalse:[
+		view origin:(0.0 @ y) corner:(1.0 @ (y + h))
+	    ].
+	    y := y + h
+	]
     ]
 !
 
@@ -578,50 +585,50 @@
     |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|
 
-            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
+	]
     ]
 !
 
@@ -631,27 +638,27 @@
     |x hw|
 
     subViews notNil ifTrue:[
-        shadowForm notNil ifTrue:[
-            hw := shadowForm width
-        ] ifFalse:[
-            hw := barHeight
-        ].
-        (handlePosition == #left) ifTrue:[
-            x := hw * 2
-        ] ifFalse:[
-            (handlePosition == #right) ifTrue:[
-                x := width - (1 "2" * hw) - margin
-            ] ifFalse:[
-                x := width // 2
-            ]
-        ].
-        (start + 1) to:stop do:[:index |
-            |view y|
+	shadowForm notNil ifTrue:[
+	    hw := shadowForm width
+	] ifFalse:[
+	    hw := barHeight
+	].
+	(handlePosition == #left) ifTrue:[
+	    x := hw * 2
+	] ifFalse:[
+	    (handlePosition == #right) ifTrue:[
+		x := width - (1 "2" * hw) - margin
+	    ] ifFalse:[
+		x := width // 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 origin y - barHeight + 1.
+	    aBlock value:(x @ y)
+	]
     ]
 !