Scroller.st
changeset 999 3c330af7516c
parent 993 51cce445b5d5
child 1009 ae6be1f683fe
--- a/Scroller.st	Tue Feb 11 22:54:28 1997 +0100
+++ b/Scroller.st	Wed Feb 12 01:24:34 1997 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1989 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,26 +11,26 @@
 "
 
 View subclass:#Scroller
-	instanceVariableNames:'thumbOrigin thumbHeight thumbColor thumbFrameColor scrollAction
-		orientation thumbFrame thumbLevel scrolling pressOffset
-		synchronousOperation shadowForm lightForm inset thumbShadowColor
-		thumbLightColor thumbEdgeStyle thumbHalfShadowColor
-		thumbHalfLightColor thumbEnteredColor thumbFrameSizeDifference
-		tallyLevel tallyMarks fixThumbHeight frameBeforeMove ghostColor
-		ghostFrameColor ghostLevel rangeStart rangeEnd rangeStep entered
-		thumbActiveLevel'
-	classVariableNames:'HandleShadowForm HandleLightForm DefaultViewBackground
-		DefaultShadowColor DefaultLightColor DefaultThumbColor
-		DefaultThumbShadowColor DefaultThumbLightColor
-		DefaultThumbHalfShadowColor DefaultThumbHalfLightColor
-		DefaultHalfShadowColor DefaultHalfLightColor DefaultTallyMarks
-		DefaultTallyLevel DefaultLevel DefaultBorderWidth
-		DefaultThumbLevel DefaultInset DefaultThumbFrameColor
-		DefaultGhostColor DefaultGhostFrameColor DefaultGhostLevel
-		DefaultFixThumbHeight DefaultEdgeStyle DefaultFullViewBackground
-		DefaultThumbEnteredColor DefaultThumbActiveLevel'
-	poolDictionaries:''
-	category:'Views-Interactors'
+        instanceVariableNames:'thumbOrigin thumbHeight thumbColor thumbFrameColor scrollAction
+                orientation thumbFrame thumbLevel scrolling pressOffset
+                synchronousOperation shadowForm lightForm inset thumbShadowColor
+                thumbLightColor thumbEdgeStyle thumbHalfShadowColor
+                thumbHalfLightColor thumbEnteredColor thumbFrameSizeDifference
+                tallyLevel tallyMarks fixThumbHeight frameBeforeMove ghostColor
+                ghostFrameColor ghostLevel rangeStart rangeEnd rangeStep entered
+                thumbActiveLevel'
+        classVariableNames:'HandleShadowForm HandleLightForm DefaultViewBackground
+                DefaultShadowColor DefaultLightColor DefaultThumbColor
+                DefaultThumbShadowColor DefaultThumbLightColor
+                DefaultThumbHalfShadowColor DefaultThumbHalfLightColor
+                DefaultHalfShadowColor DefaultHalfLightColor DefaultTallyMarks
+                DefaultTallyLevel DefaultLevel DefaultBorderWidth
+                DefaultThumbLevel DefaultInset DefaultThumbFrameColor
+                DefaultGhostColor DefaultGhostFrameColor DefaultGhostLevel
+                DefaultFixThumbHeight DefaultEdgeStyle DefaultFullViewBackground
+                DefaultThumbEnteredColor DefaultThumbActiveLevel'
+        poolDictionaries:''
+        category:'Views-Interactors'
 !
 
 !Scroller class methodsFor:'documentation'!
@@ -38,7 +38,7 @@
 copyright
 "
  COPYRIGHT (c) 1989 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
@@ -86,14 +86,14 @@
     thumbColor                  <Color>         color of thumb
     thumbFrameColor             <Color>         color of the frame around the thumb
     scrollAction                <Block>         1 arg block to be evaluated when scrolled
-						(arg is position in percent)
+                                                (arg is position in percent)
     orientation                 <Symbol>        #horizontal or #vertical
     thumbFrame                  <Rectangle>     frame of thumb in pixels (cached)
     thumbLevel                  <Number>        level of thumb if 3d
     scrolling                   <Boolean>       true during scroll
     pressOffset                 <Number>        temporary (offset into frame when move started)
     synchronousOperation        <Boolean>       true if synchronous (i.e. dont wait till release
-						to perform action)
+                                                to perform action)
     shadowForm                  <Form>          bitmap of knob if any (shadow part)
     lightForm                   <Form>          bitmap of knob if any (light part)
     inset                       <Integer>       number of pixels to inset thumb from view borders
@@ -103,10 +103,10 @@
     thumbHalfShadowColor        <Color>         used to draw smooth edges
     thumbHalfLightColor         <Color>         used to draw smooth edges
     thumbFrameSizeDifference    <Integer>       number of pixels the thumb is larger than 
-						it should be (can be negative for mswin-style)
+                                                it should be (can be negative for mswin-style)
     tallyLevel                  <Integer>       if not zero, specifies if tally-marks should
-						go into or out of the display (actually only <0/>0 is checked)
-						I dont know of a better word for these ...
+                                                go into or out of the display (actually only <0/>0 is checked)
+                                                I dont know of a better word for these ...
     tallyMarks                  <Integer>       number of tally marks
     fixThumbHeight              <Boolean>       perform 'wrong' height computation a la mswindows
     rangeStart                  <Number>        the range of the scroller
@@ -143,131 +143,131 @@
     if you dont like that (I do not :-), set scrollerThumbFixHeight to false (in the StyleSheet).
 
     [author:]
-	Claus Gittinger
+        Claus Gittinger
 
     [see also:]
-	ScrollBar
-	ScrollableView HVScrollableView
+        ScrollBar
+        ScrollableView HVScrollableView
 "
 !
 
 examples
 "
     basic scroller setup:
-									[exBegin]
-	|top s|
+                                                                        [exBegin]
+        |top s|
 
-	top := StandardSystemView new extent:200@200.
-	s := Scroller in:top.
-	s origin:(0.0@0.0) corner:(20@1.0).
-	s thumbHeight:10.  'percent'.     
-	top open
-									[exEnd]
+        top := StandardSystemView new extent:200@200.
+        s := Scroller in:top.
+        s origin:(0.0@0.0) corner:(20@1.0).
+        s thumbHeight:10.  'percent'.     
+        top open
+                                                                        [exEnd]
 
     setting its thumb-height:
-									[exBegin]
-	|top s|
+                                                                        [exBegin]
+        |top s|
 
-	top := StandardSystemView new extent:200@200.
-	s := Scroller in:top.
-	s origin:(0.0@0.0) corner:(20@1.0).
-	s thumbHeight:50.  'percent'.     
-	top open
-									[exEnd]
+        top := StandardSystemView new extent:200@200.
+        s := Scroller in:top.
+        s origin:(0.0@0.0) corner:(20@1.0).
+        s thumbHeight:50.  'percent'.     
+        top open
+                                                                        [exEnd]
 
     setting its thumb-origin:
-									[exBegin]
-	|top s|
+                                                                        [exBegin]
+        |top s|
 
-	top := StandardSystemView new extent:200@200.
-	s := Scroller in:top.
-	s origin:(0.0@0.0) corner:(20@1.0).
-	s thumbHeight:10.  'percent'.     
-	s thumbOrigin:30.  'percent'.     
-	top open
-									[exEnd]
+        top := StandardSystemView new extent:200@200.
+        s := Scroller in:top.
+        s origin:(0.0@0.0) corner:(20@1.0).
+        s thumbHeight:10.  'percent'.     
+        s thumbOrigin:30.  'percent'.     
+        top open
+                                                                        [exEnd]
 
     a scroller with action block (ST/X style):
-									[exBegin]
-	|top s|
+                                                                        [exBegin]
+        |top s|
 
-	top := StandardSystemView new extent:200@200.
-	s := Scroller in:top.
-	s origin:(0.0@0.0) corner:(20@1.0).
-	s thumbHeight:10.  'percent'.     
-	s scrollAction:[:percent | Transcript show:'moved to: '; showCR:percent asFloat].
-	top open
-									[exEnd]
+        top := StandardSystemView new extent:200@200.
+        s := Scroller in:top.
+        s origin:(0.0@0.0) corner:(20@1.0).
+        s thumbHeight:10.  'percent'.     
+        s scrollAction:[:percent | Transcript show:'moved to: '; showCR:percent asFloat].
+        top open
+                                                                        [exEnd]
 
     setting its range:
-									[exBegin]
-	|top s|
+                                                                        [exBegin]
+        |top s|
 
-	top := StandardSystemView new extent:200@200.
-	s := Scroller in:top.
-	s origin:(0.0@0.0) corner:(20@1.0).
-	s thumbHeight:10.  'percent'.     
-	s scrollAction:[:percent | Transcript show:'moved to: '; showCR:percent asFloat].
-	s start:0 stop:1.
-	top open
-									[exEnd]
+        top := StandardSystemView new extent:200@200.
+        s := Scroller in:top.
+        s origin:(0.0@0.0) corner:(20@1.0).
+        s thumbHeight:10.  'percent'.     
+        s scrollAction:[:percent | Transcript show:'moved to: '; showCR:percent asFloat].
+        s start:0 stop:1.
+        top open
+                                                                        [exEnd]
 
     create a scroller in its default extent and have it positioned
     at the side; beside another view:
-									[exBegin]
-	|top s v|
+                                                                        [exBegin]
+        |top s v|
 
-	top := StandardSystemView new extent:200@200.
-	s := Scroller in:top.
-	s origin:(0.0@0.0) corner:(0.0@1.0).
-	s rightInset:(s preferredExtent x negated).
-	s thumbHeight:10.
-	s level:1.
+        top := StandardSystemView new extent:200@200.
+        s := Scroller in:top.
+        s origin:(0.0@0.0) corner:(0.0@1.0).
+        s rightInset:(s preferredExtent x negated).
+        s thumbHeight:10.
+        s level:1.
 
-	v := View in:top.
-	v origin:0.0@0.0 corner:1.0@1.0.
-	v leftInset:(s preferredExtent x).
-	v viewBackground:Color red.
-	v level:2.
+        v := View in:top.
+        v origin:0.0@0.0 corner:1.0@1.0.
+        v leftInset:(s preferredExtent x).
+        v viewBackground:Color red.
+        v level:2.
 
-	top open
-									[exEnd]
+        top open
+                                                                        [exEnd]
 
     using a model (ST-80 style):
-									[exBegin]
-	|top s m|
+                                                                        [exBegin]
+        |top s m|
 
-	m := 0 asValue.
-	InspectorView openOn:m monitor:'value'.  'look at value'.
+        m := 0 asValue.
+        InspectorView openOn:m monitor:'value'.  'look at value'.
 
-	top := StandardSystemView new extent:200@200.
-	s := Scroller in:top.
-	s origin:(0.0@0.0) corner:(20@1.0).
-	s thumbHeight:10.  'percent'.     
-	s model:m.
-	top open
-									[exEnd]
+        top := StandardSystemView new extent:200@200.
+        s := Scroller in:top.
+        s origin:(0.0@0.0) corner:(20@1.0).
+        s thumbHeight:10.  'percent'.     
+        s model:m.
+        top open
+                                                                        [exEnd]
 
     using a different changeSelector:
-									[exBegin]
-	|top s1 s2 m|
+                                                                        [exBegin]
+        |top s1 s2 m|
 
-	m := Plug new.
-	m respondTo:#value1: with:[:v | Transcript show:'scroller 1 moved to: '; showCR:v].
-	m respondTo:#value2: with:[:v | Transcript show:'scroller 2 moved to: '; showCR:v].
+        m := Plug new.
+        m respondTo:#value1: with:[:v | Transcript show:'scroller 1 moved to: '; showCR:v].
+        m respondTo:#value2: with:[:v | Transcript show:'scroller 2 moved to: '; showCR:v].
 
-	top := StandardSystemView new extent:200@200.
-	s1 := Scroller in:top.
-	s1 origin:(0.0@0.0) corner:(20@1.0).
-	s1 thumbHeight:10.  'percent'.     
-	s1 model:m; change:#value1:.
+        top := StandardSystemView new extent:200@200.
+        s1 := Scroller in:top.
+        s1 origin:(0.0@0.0) corner:(20@1.0).
+        s1 thumbHeight:10.  'percent'.     
+        s1 model:m; change:#value1:.
 
-	s2 := Scroller in:top.
-	s2 origin:(30@0.0) corner:(50@1.0).
-	s2 thumbHeight:10.  'percent'.     
-	s2 model:m; change:#value2:.
-	top open
-									[exEnd]
+        s2 := Scroller in:top.
+        s2 origin:(30@0.0) corner:(50@1.0).
+        s2 thumbHeight:10.  'percent'.     
+        s2 model:m; change:#value2:.
+        top open
+                                                                        [exEnd]
 "
 ! !
 
@@ -335,17 +335,17 @@
     "extract values from the styleSheet and cache them in class variables"
 
     <resource: #style (#scrollerViewBackground #scrollerFullViewBackground
-		       #scrollerThumbColor 
-		       #scrollerShadowColor #scrollerLightColor
-		       #scrollerThumbShadowColor #scrollerThumbLightColor
-		       #scrollerThumbHalfShadowColor #scrollerThumbHalfLightColor
-		       #scrollerThumbFrameColor #scrollerGhostColor
-		       #scrollerGhostLevel #scrollerGhostFrameColor
-		       #scrollerNTallyMarks #scrollerTallyLevel
-		       #scrollerLevel #scrollerBorderWidth
-		       #scrollerThumbLevel #scrollerThumbInset
-		       #scrollerThumbFixHeight #scrollerThumbEdgeStyle
-		       #scrollerThumbEnteredColor #scrollerThumbActiveLevel )>
+                       #scrollerThumbColor 
+                       #scrollerShadowColor #scrollerLightColor
+                       #scrollerThumbShadowColor #scrollerThumbLightColor
+                       #scrollerThumbHalfShadowColor #scrollerThumbHalfLightColor
+                       #scrollerThumbFrameColor #scrollerGhostColor
+                       #scrollerGhostLevel #scrollerGhostFrameColor
+                       #scrollerNTallyMarks #scrollerTallyLevel
+                       #scrollerLevel #scrollerBorderWidth
+                       #scrollerThumbLevel #scrollerThumbInset
+                       #scrollerThumbFixHeight #scrollerThumbEdgeStyle
+                       #scrollerThumbEnteredColor #scrollerThumbActiveLevel )>
 
     DefaultViewBackground := StyleSheet colorAt:'scrollerViewBackground'.
     DefaultFullViewBackground := StyleSheet colorAt:'scrollerFullViewBackground'.
@@ -364,7 +364,7 @@
     DefaultTallyMarks := StyleSheet at:'scrollerNTallyMarks' default:0.
     DefaultTallyLevel := 0.
     DefaultTallyMarks ~~ 0 ifTrue:[
-	DefaultTallyLevel := StyleSheet at:'scrollerTallyLevel' default:1.
+        DefaultTallyLevel := StyleSheet at:'scrollerTallyLevel' default:1.
     ].
     DefaultLevel := StyleSheet at:'scrollerLevel' default:0.
     DefaultBorderWidth := StyleSheet at:'scrollerBorderWidth' default:(StyleSheet at:'borderWidth').
@@ -375,10 +375,10 @@
     DefaultEdgeStyle := StyleSheet at:'scrollerThumbEdgeStyle'.
 
     StyleSheet fileReadFailed ifTrue:[
-	DefaultViewBackground := Grey.
-	DefaultThumbColor := White.
-	DefaultThumbFrameColor := Black.
-	DefaultInset := 1.
+        DefaultViewBackground := Grey.
+        DefaultThumbColor := White.
+        DefaultThumbFrameColor := Black.
+        DefaultInset := 1.
     ]
 
     "Modified: 20.3.1996 / 16:26:44 / cg"
@@ -489,43 +489,43 @@
     newHeight := aNumber / (rangeEnd - rangeStart / 100).
 
     (newHeight > 100) ifTrue:[
-	realNewHeight := 100
+        realNewHeight := 100
     ] ifFalse:[
-	realNewHeight := newHeight
+        realNewHeight := newHeight
     ].
     ((realNewHeight ~= thumbHeight) or:[thumbFrame isNil]) ifTrue:[
-	thumbHeight := realNewHeight.
+        thumbHeight := realNewHeight.
 
-	(DefaultFullViewBackground notNil
-	and:[DefaultViewBackground notNil
-	and:[DefaultFullViewBackground ~~ DefaultViewBackground]]) ifTrue:[
-	    realNewHeight >= 100 ifTrue:[
-		nBg := DefaultFullViewBackground.
-	    ] ifFalse:[
-		nBg := DefaultViewBackground
-	    ].
-	    nBg := nBg on:device.
-	    nBg ~~ viewBackground ifTrue:[
-		self viewBackground:nBg.
-		shown ifTrue:[self clear].
-	    ]
-	].
+        (DefaultFullViewBackground notNil
+        and:[DefaultViewBackground notNil
+        and:[DefaultFullViewBackground ~~ DefaultViewBackground]]) ifTrue:[
+            realNewHeight >= 100 ifTrue:[
+                nBg := DefaultFullViewBackground.
+            ] ifFalse:[
+                nBg := DefaultViewBackground
+            ].
+            nBg := nBg on:device.
+            nBg ~~ viewBackground ifTrue:[
+                self viewBackground:nBg.
+                shown ifTrue:[self clear].
+            ]
+        ].
 
-	shown ifTrue:[
-	    oldFrame := thumbFrame.
-	    self computeThumbFrame.
-	    (fixThumbHeight or:[oldFrame ~~ thumbFrame]) ifTrue:[
-		oldFrame notNil ifTrue:[
-		    self drawThumbBackgroundInX:(oldFrame left)
-					      y:(oldFrame top) 
-					  width:(oldFrame width) 
-					 height:(oldFrame height).
-		].
-		self drawThumb
-	    ]
-	] ifFalse:[
-	    thumbFrame := nil
-	]
+        shown ifTrue:[
+            oldFrame := thumbFrame.
+            self computeThumbFrame.
+            (fixThumbHeight or:[oldFrame ~~ thumbFrame]) ifTrue:[
+                oldFrame notNil ifTrue:[
+                    self drawThumbBackgroundInX:(oldFrame left)
+                                              y:(oldFrame top) 
+                                          width:(oldFrame width) 
+                                         height:(oldFrame height).
+                ].
+                self drawThumb
+            ]
+        ] ifFalse:[
+            thumbFrame := nil
+        ]
     ]
 !
 
@@ -697,61 +697,61 @@
     newHeight := heightNumber / (rangeEnd - rangeStart / 100).
 
     (newHeight > 100) ifTrue:[
-	realNewHeight := 100
+        realNewHeight := 100
     ] ifFalse:[
-	realNewHeight := newHeight
+        realNewHeight := newHeight
     ].
     ((newOrigin + realNewHeight) > 100) ifTrue:[
-	realNewOrigin := 100 - realNewHeight
+        realNewOrigin := 100 - realNewHeight
     ] ifFalse: [
-	realNewOrigin := newOrigin
+        realNewOrigin := newOrigin
     ].
     (realNewOrigin < 0) ifTrue: [
-	realNewOrigin := 0
+        realNewOrigin := 0
     ].
 
     changed := (realNewHeight ~= thumbHeight) or:[realNewOrigin ~= thumbOrigin].
     (changed or:[thumbFrame isNil]) ifTrue:[
-	old := self absFromPercent:thumbOrigin.
-	new := self absFromPercent:realNewOrigin.
-	changed := old ~~ new.
-	changed ifFalse:[
-	    old := self absFromPercent:thumbHeight.
-	    new := self absFromPercent:realNewHeight.
-	    changed := (old ~~ new)
-	].
-	(changed or:[thumbFrame isNil]) ifTrue:[
-	    thumbOrigin := realNewOrigin.
-	    thumbHeight := realNewHeight.
+        old := self absFromPercent:thumbOrigin.
+        new := self absFromPercent:realNewOrigin.
+        changed := old ~~ new.
+        changed ifFalse:[
+            old := self absFromPercent:thumbHeight.
+            new := self absFromPercent:realNewHeight.
+            changed := (old ~~ new)
+        ].
+        (changed or:[thumbFrame isNil]) ifTrue:[
+            thumbOrigin := realNewOrigin.
+            thumbHeight := realNewHeight.
 
-	    (DefaultFullViewBackground notNil
-	    and:[DefaultViewBackground notNil
-	    and:[DefaultFullViewBackground ~~ DefaultViewBackground]]) ifTrue:[
-		realNewHeight >= 100 ifTrue:[
-		    nBg := DefaultFullViewBackground.
-		] ifFalse:[
-		    nBg := DefaultViewBackground
-		].
-		nBg := nBg on:device.
-		nBg ~~ viewBackground ifTrue:[
-		    self viewBackground:nBg.
-		    shown ifTrue:[self clear].
-		]
-	    ].
+            (DefaultFullViewBackground notNil
+            and:[DefaultViewBackground notNil
+            and:[DefaultFullViewBackground ~~ DefaultViewBackground]]) ifTrue:[
+                realNewHeight >= 100 ifTrue:[
+                    nBg := DefaultFullViewBackground.
+                ] ifFalse:[
+                    nBg := DefaultViewBackground
+                ].
+                nBg := nBg on:device.
+                nBg ~~ viewBackground ifTrue:[
+                    self viewBackground:nBg.
+                    shown ifTrue:[self clear].
+                ]
+            ].
 
-	    shown ifTrue:[
-		thumbFrame notNil ifTrue:[
-		    self drawThumbBackgroundInX:(thumbFrame left)
-					      y:(thumbFrame top) 
-					  width:(thumbFrame width) 
-					 height:(thumbFrame height).
-		].
-		self computeThumbFrame.
-		self drawThumb
-	    ] ifFalse:[
-		thumbFrame := nil
-	    ]
-	]
+            shown ifTrue:[
+                thumbFrame notNil ifTrue:[
+                    self drawThumbBackgroundInX:(thumbFrame left)
+                                              y:(thumbFrame top) 
+                                          width:(thumbFrame width) 
+                                         height:(thumbFrame height).
+                ].
+                self computeThumbFrame.
+                self drawThumb
+            ] ifFalse:[
+                thumbFrame := nil
+            ]
+        ]
     ]
 ! !
 
@@ -873,9 +873,9 @@
 
     (thumbHeight >= 100) ifTrue:[^ self].
     orientation == #vertical ifTrue:[
-	thumbFrame height >= height ifTrue:[^ self].
+        thumbFrame height >= height ifTrue:[^ self].
     ] ifFalse:[
-	thumbFrame width >= width ifTrue:[^ self].
+        thumbFrame width >= width ifTrue:[^ self].
     ].
 
     l := thumbFrame left.
@@ -888,113 +888,113 @@
 
     lvl := thumbLevel.
     scrolling ifTrue:[
-	lvl := thumbActiveLevel
+        lvl := thumbActiveLevel
     ].
 
     lvl == 0 ifTrue:[
-	thumbFrameColor notNil ifTrue:[
-	    self paint:thumbFrameColor.
-	    self displayRectangle:thumbFrame.
-	].
-	^ self
+        thumbFrameColor notNil ifTrue:[
+            self paint:thumbFrameColor.
+            self displayRectangle:thumbFrame.
+        ].
+        ^ self
     ].
 
     "what a kludge - must be a parameter to drawEdge..."
     self drawEdgesForX:l y:t width:w height:h level:lvl
-		shadow:thumbShadowColor light:thumbLightColor
-		halfShadow:thumbHalfShadowColor halfLight:thumbHalfLightColor
-		style:thumbEdgeStyle.
+                shadow:thumbShadowColor light:thumbLightColor
+                halfShadow:thumbHalfShadowColor halfLight:thumbHalfLightColor
+                style:thumbEdgeStyle.
 
     thumbFrameColor notNil ifTrue:[
-	self paint:thumbFrameColor.
-	orientation == #vertical ifTrue:[
-	    self displayRectangleX:l y:t width:w"-1" height:h.
-	] ifFalse:[
-	    self displayRectangleX:l y:t width:w height:h"-1".
-	]
+        self paint:thumbFrameColor.
+        orientation == #vertical ifTrue:[
+            self displayRectangleX:l y:t width:w"-1" height:h.
+        ] ifFalse:[
+            self displayRectangleX:l y:t width:w height:h"-1".
+        ]
     ].
 
     (tallyLevel == 0 or:[tallyMarks == 0]) ifTrue:[
-	shadowForm notNil ifTrue:[
-	    handleX := l + ((w - 8) // 2).
-	    handleY := t + ((h - 8) // 2).
-	    self drawHandleFormAtX:handleX y:handleY
-	].
-	^ self
+        shadowForm notNil ifTrue:[
+            handleX := l + ((w - 8) // 2).
+            handleY := t + ((h - 8) // 2).
+            self drawHandleFormAtX:handleX y:handleY
+        ].
+        ^ self
     ].
 
     "iris style - draw tallys"
 
     tallyLevel > 0 ifTrue:[
-	color1 := thumbLightColor.
-	color2 := thumbShadowColor.
+        color1 := thumbLightColor.
+        color2 := thumbShadowColor.
     ] ifFalse:[
-	color1 := thumbShadowColor.
-	color2 := thumbLightColor.
+        color1 := thumbShadowColor.
+        color2 := thumbLightColor.
     ].
 
     "draw tally marks"
 
     (orientation == #vertical) ifTrue:[
-	self paint:color1.
-	y := t + (h // 2) - 1.
-	xL := l + lvl - 1.
-	xR := l + w - lvl "+ 1".
-	self displayLineFromX:xL y:y toX:xR y:y.
-	y := y + 1.
-	self paint:color2.
-	self displayLineFromX:xL y:y toX:xR y:y.
+        self paint:color1.
+        y := t + (h // 2) - 1.
+        xL := l + lvl - 1.
+        xR := l + w - lvl "+ 1".
+        self displayLineFromX:xL y:y toX:xR y:y.
+        y := y + 1.
+        self paint:color2.
+        self displayLineFromX:xL y:y toX:xR y:y.
 
-	tallyMarks > 1 ifTrue:[
-	    "dont draw other marks if there is not enough space"
+        tallyMarks > 1 ifTrue:[
+            "dont draw other marks if there is not enough space"
 
-	    mm := device verticalPixelPerMillimeter rounded.
-	    h > (mm * (tallyMarks * 2)) ifTrue:[
-		y := y - 1 - mm.
-		self paint:color1.
-		self displayLineFromX:xL y:y toX:xR y:y.
-		y := y + 1.
-		self paint:color2.
-		self displayLineFromX:xL y:y toX:xR y:y.
+            mm := device verticalPixelPerMillimeter rounded.
+            h > (mm * (tallyMarks * 2)) ifTrue:[
+                y := y - 1 - mm.
+                self paint:color1.
+                self displayLineFromX:xL y:y toX:xR y:y.
+                y := y + 1.
+                self paint:color2.
+                self displayLineFromX:xL y:y toX:xR y:y.
 
-		y := y - 1 + mm + mm.
-		self paint:color1.
-		self displayLineFromX:xL y:y toX:xR y:y.
-		y := y + 1.
-		self paint:color2.
-		self displayLineFromX:xL y:y toX:xR y:y
-	    ]
-	]
+                y := y - 1 + mm + mm.
+                self paint:color1.
+                self displayLineFromX:xL y:y toX:xR y:y.
+                y := y + 1.
+                self paint:color2.
+                self displayLineFromX:xL y:y toX:xR y:y
+            ]
+        ]
     ] ifFalse:[
-	x := l + (w // 2) - 1.
-	yT := t + lvl - 1.
-	yB := t + h - lvl "+ 1".
-	self paint:color1.
-	self displayLineFromX:x y:yT toX:x y:yB.
-	self paint:color2.
-	x := x + 1.
-	self displayLineFromX:x y:yT toX:x y:yB.
+        x := l + (w // 2) - 1.
+        yT := t + lvl - 1.
+        yB := t + h - lvl "+ 1".
+        self paint:color1.
+        self displayLineFromX:x y:yT toX:x y:yB.
+        self paint:color2.
+        x := x + 1.
+        self displayLineFromX:x y:yT toX:x y:yB.
 
-	tallyMarks > 1 ifTrue:[
-	    "dont draw other marks if there is not enough space"
+        tallyMarks > 1 ifTrue:[
+            "dont draw other marks if there is not enough space"
 
-	    mm := device horizontalPixelPerMillimeter rounded.
-	    w > (mm * (tallyMarks * 2)) ifTrue:[
-		x := x - 1 - mm.
-		self paint:color1.
-		self displayLineFromX:x y:yT toX:x y:yB.
-		x := x + 1.
-		self paint:color2.
-		self displayLineFromX:x y:yT toX:x y:yB.
+            mm := device horizontalPixelPerMillimeter rounded.
+            w > (mm * (tallyMarks * 2)) ifTrue:[
+                x := x - 1 - mm.
+                self paint:color1.
+                self displayLineFromX:x y:yT toX:x y:yB.
+                x := x + 1.
+                self paint:color2.
+                self displayLineFromX:x y:yT toX:x y:yB.
 
-		x := x - 1 + mm + mm.
-		self paint:color1.
-		self displayLineFromX:x y:yT toX:x y:yB.
-		x := x + 1.
-		self paint:color2.
-		self displayLineFromX:x y:yT toX:x y:yB
-	    ]
-	]
+                x := x - 1 + mm + mm.
+                self paint:color1.
+                self displayLineFromX:x y:yT toX:x y:yB.
+                x := x + 1.
+                self paint:color2.
+                self displayLineFromX:x y:yT toX:x y:yB
+            ]
+        ]
     ]
 
     "Modified: 20.3.1996 / 10:55:29 / cg"
@@ -1046,45 +1046,45 @@
     |pos curr limit prevOrigin newOrigin in|
 
     scrolling ifFalse: [
-	self highlightThumbForPointerX:x y:y.
-	^ self              
+        self highlightThumbForPointerX:x y:y.
+        ^ self              
     ].              
 
     entered := true.
     frameBeforeMove isNil ifTrue:[
-	(ghostColor notNil 
-	or:[ghostFrameColor notNil
-	or:[ghostLevel ~~ 0]]) ifTrue:[
-	    frameBeforeMove := thumbFrame insetBy:1@1
-	]
+        (ghostColor notNil 
+        or:[ghostFrameColor notNil
+        or:[ghostLevel ~~ 0]]) ifTrue:[
+            frameBeforeMove := thumbFrame insetBy:1@1
+        ]
     ].
 
     (orientation == #vertical) ifTrue:[
-	curr := y.
-	limit := height
+        curr := y.
+        limit := height
     ] ifFalse:[
-	curr := x.
-	limit := width
+        curr := x.
+        limit := width
     ].
 
     (curr < 0) ifTrue:[                        "check against limits"
-	pos := 0
+        pos := 0
     ] ifFalse:[
-	(curr > limit) ifTrue:[
-	    pos := limit
-	] ifFalse:[
-	    pos := curr
-	]
+        (curr > limit) ifTrue:[
+            pos := limit
+        ] ifFalse:[
+            pos := curr
+        ]
     ].
 
     prevOrigin := self thumbOrigin.
     newOrigin := self percentFromAbs:(pos - pressOffset).
     prevOrigin ~= newOrigin ifTrue:[
-	self thumbOrigin:newOrigin.
+        self thumbOrigin:newOrigin.
 
-	synchronousOperation ifTrue: [
-	    self tellOthers.
-	]
+        synchronousOperation ifTrue: [
+            self tellOthers.
+        ]
     ]
 
     "Modified: 6.3.1996 / 17:35:26 / cg"
@@ -1140,34 +1140,34 @@
     |rect mustDrawThumb|
 
     scrolling ifTrue:[
-	thumbFrame notNil ifTrue:[
-	    mustDrawThumb := false.
-	    scrolling := false.
+        thumbFrame notNil ifTrue:[
+            mustDrawThumb := false.
+            scrolling := false.
 
-	    frameBeforeMove notNil ifTrue:[
-		rect := frameBeforeMove.
-		frameBeforeMove := nil.
-		self drawThumbBackgroundInX:rect left
-					  y:rect top
-				      width:rect width 
-				     height:rect height.
+            frameBeforeMove notNil ifTrue:[
+                rect := frameBeforeMove.
+                frameBeforeMove := nil.
+                self drawThumbBackgroundInX:rect left
+                                          y:rect top
+                                      width:rect width 
+                                     height:rect height.
 
-		(rect intersects:thumbFrame) ifTrue:[
-		    mustDrawThumb := true.
-		]
-	    ].
-	    thumbLevel ~~ thumbActiveLevel ifTrue:[
-		mustDrawThumb := true
-	    ].
-	    mustDrawThumb ifTrue:[
-		self drawThumb
-	    ].    
+                (rect intersects:thumbFrame) ifTrue:[
+                    mustDrawThumb := true.
+                ]
+            ].
+            thumbLevel ~~ thumbActiveLevel ifTrue:[
+                mustDrawThumb := true
+            ].
+            mustDrawThumb ifTrue:[
+                self drawThumb
+            ].    
 
 "/            scrolling := false.
-	    synchronousOperation ifFalse: [
-		self tellOthers.
-	    ]
-	]
+            synchronousOperation ifFalse: [
+                self tellOthers.
+            ]
+        ]
     ]
 
     "Modified: 20.3.1996 / 10:58:25 / cg"
@@ -1179,25 +1179,25 @@
     |pos curr curr2 limit1 limit2|
 
     (orientation == #vertical) ifTrue:[
-	curr := y.
-	curr2 := y - (thumbFrame height // 2).
-	limit1 := height.
-	limit2 := thumbFrame top
+        curr := y.
+        curr2 := y - (thumbFrame height // 2).
+        limit1 := height.
+        limit2 := thumbFrame top
     ] ifFalse:[
-	curr := x.
-	curr2 := x - (thumbFrame width // 2).
-	limit1 := width.
-	limit2 := thumbFrame left
+        curr := x.
+        curr2 := x - (thumbFrame width // 2).
+        limit1 := width.
+        limit2 := thumbFrame left
     ].
 
     (curr2 < 0) ifTrue:[                        "check against limits"
-	pos := 0
+        pos := 0
     ] ifFalse:[
-	(curr2 > limit1) ifTrue:[
-	    pos := limit1
-	] ifFalse:[
-	    pos := curr2
-	]
+        (curr2 > limit1) ifTrue:[
+            pos := limit1
+        ] ifFalse:[
+            pos := curr2
+        ]
     ].
 
     frameBeforeMove := thumbFrame insetBy:1@1.
@@ -1206,9 +1206,9 @@
     self tellOthers.
 
     (orientation == #vertical) ifTrue:[
-	limit2 := thumbFrame top
+        limit2 := thumbFrame top
     ] ifFalse:[
-	limit2 := thumbFrame left
+        limit2 := thumbFrame left
     ].
     pressOffset := curr - limit2.
     scrolling := true
@@ -1222,11 +1222,11 @@
     in := self thumbFrame containsPoint:(x@y).
     (in ~~ entered 
     or:[thumbLevel ~~ thumbActiveLevel]) ifTrue:[
-	entered := in.
-	(thumbColor ~~ thumbEnteredColor 
-	or:[thumbLevel ~~ thumbActiveLevel]) ifTrue: [
-	    self drawThumb
-	].
+        entered := in.
+        (thumbColor ~~ thumbEnteredColor 
+        or:[thumbLevel ~~ thumbActiveLevel]) ifTrue: [
+            self drawThumb
+        ].
     ].
 
     "Created: 6.3.1996 / 17:35:07 / cg"
@@ -1296,8 +1296,8 @@
 
     (changedObject == model 
     "and:[something == aspectMsg]") ifTrue:[
-	self thumbOrigin:(model value).
-	^ self
+        self thumbOrigin:(model value).
+        ^ self
     ].
     super update:something with:aParameter from:changedObject
 ! !
@@ -1346,7 +1346,7 @@
      the ST/X way of notifying scrolls
     "
     scrollAction notNil ifTrue:[
-	scrollAction value:org 
+        scrollAction value:org 
     ].
     "
      the ST-80 way of notifying scrolls
@@ -1550,7 +1550,7 @@
 realize
     super realize.
     model notNil ifTrue:[
-	self thumbOrigin:(model value).
+        self thumbOrigin:(model value).
     ].
 ! !
 
@@ -1562,9 +1562,9 @@
     |fullSize|
 
     (orientation == #vertical) ifTrue:[
-	fullSize := height
+        fullSize := height
     ] ifFalse:[
-	fullSize := width
+        fullSize := width
     ].
 "/    ^ ((percent * (fullSize - (margin * 2))) / 100) rounded
 "/ 20-apr-94
@@ -1586,11 +1586,11 @@
     newPos1 := (self absFromPercent:thumbOrigin) + margin.
     newSize1 := computedSize := self absFromPercent:thumbHeight.
     (orientation == #vertical) ifTrue:[
-	sz1 := height.
-	sz2 := width
+        sz1 := height.
+        sz2 := width
     ] ifFalse:[
-	sz1 := width.
-	sz2 := height
+        sz1 := width.
+        sz2 := height
     ].
 
     "
@@ -1600,68 +1600,68 @@
     newSize2 := sz2 - (2 * newPos2).
 "/    (style ~~ #normal) ifTrue:[
     thumbLevel ~~ 0 ifTrue:[
-	"
-	 do not make thumb too small (for handle & to be catchable)
-	"
-	minSz := 10 + (2 * thumbLevel)
+        "
+         do not make thumb too small (for handle & to be catchable)
+        "
+        minSz := 10 + (2 * thumbLevel)
     ] ifFalse:[
-	"
-	 do not make thumb too small (uncatchable)
-	"
-	minSz := 4
+        "
+         do not make thumb too small (uncatchable)
+        "
+        minSz := 4
     ].
 
     (newSize1 < minSz) ifTrue:[
-	newSize1 := minSz.
-	thumbFrameSizeDifference := newSize1 - computedSize
+        newSize1 := minSz.
+        thumbFrameSizeDifference := newSize1 - computedSize
     ] ifFalse:[
-	thumbFrameSizeDifference := 0.
+        thumbFrameSizeDifference := 0.
     ].
 
     fixThumbHeight ifTrue:[
-	"have a fix-size thumb (i.e. mswindows style)"
+        "have a fix-size thumb (i.e. mswindows style)"
 
-	newSize1 := sz2 - (2 * inset).   "make it square"
-	thumbFrameSizeDifference := newSize1 - computedSize.
+        newSize1 := sz2 - (2 * inset).   "make it square"
+        thumbFrameSizeDifference := newSize1 - computedSize.
     ].
 
     "
      oops - if height does not relect real visibible area, we have to adjust the origin
     "
     (thumbFrameSizeDifference == 0) ifFalse:[
-	newPos1 := (self absFromPercent:thumbOrigin) + margin.
+        newPos1 := (self absFromPercent:thumbOrigin) + margin.
 "/        newPos1 := ((thumbOrigin * (sz1 - thumbFrameSizeDifference - (margin * 2))) / 100) rounded + margin
     ].
 
     (orientation == #vertical) ifTrue:[
-	ny := newPos1.
-	nx := newPos2.
-	nh := newSize1.
-	nw := newSize2.
-	ny + nh + margin > height ifTrue:[
-	    ny := height - margin - nh
-	]
+        ny := newPos1.
+        nx := newPos2.
+        nh := newSize1.
+        nw := newSize2.
+        ny + nh + margin > height ifTrue:[
+            ny := height - margin - nh
+        ]
     ] ifFalse:[
-	nx := newPos1.
-	ny := newPos2.
-	nw := newSize1.
-	nh := newSize2.
-	nx + nw + margin > width ifTrue:[
-	    nx := width - margin - nw
-	]
+        nx := newPos1.
+        ny := newPos2.
+        nw := newSize1.
+        nh := newSize2.
+        nx + nw + margin > width ifTrue:[
+            nx := width - margin - nw
+        ]
     ].
 
     "
      do not create new Rectangle if its the same anyway
     "
     thumbFrame notNil ifTrue:[
-	(ny == thumbFrame top) ifTrue:[
-	  (nx == thumbFrame left) ifTrue:[
-	    (nh == thumbFrame height) ifTrue:[
-	      (nw == thumbFrame width) ifTrue:[ ^ self]
-	    ]
-	  ]
-	]
+        (ny == thumbFrame top) ifTrue:[
+          (nx == thumbFrame left) ifTrue:[
+            (nh == thumbFrame height) ifTrue:[
+              (nw == thumbFrame width) ifTrue:[ ^ self]
+            ]
+          ]
+        ]
     ].
     thumbFrame := Rectangle left:nx top:ny width:nw height:nh
 !
@@ -1672,17 +1672,17 @@
     |fullSize val t|
 
     (orientation == #vertical) ifTrue:[
-	fullSize := height
+        fullSize := height
     ] ifFalse:[
-	fullSize := width
+        fullSize := width
     ].
 
     t := fullSize - thumbFrameSizeDifference - (margin * 2).
     t = 0 ifTrue:[
-	"/ in rare cases, this happens ...
-	val := 0
+        "/ in rare cases, this happens ...
+        val := 0
     ] ifFalse:[
-	val := absValue / t * (rangeEnd - rangeStart).
+        val := absValue / t * (rangeEnd - rangeStart).
     ].
     val := val + rangeStart.
 
@@ -1703,52 +1703,52 @@
      get the content's size
     "
     aView isNil ifTrue:[
-	contentsSize := 0
+        contentsSize := 0
     ] ifFalse:[
-	orientation == #vertical ifTrue:[
-	    contentsSize := aView heightOfContents.
-	    aView transformation notNil ifTrue:[
-		contentsSize := aView transformation applyScaleY:contentsSize.
-	    ].
-	] ifFalse:[
-	    contentsSize := aView widthOfContents.
-	    aView transformation notNil ifTrue:[
-		contentsSize := aView transformation applyScaleX:contentsSize.
-	    ].
-	]
+        orientation == #vertical ifTrue:[
+            contentsSize := aView heightOfContents.
+            aView transformation notNil ifTrue:[
+                contentsSize := aView transformation applyScaleY:contentsSize.
+            ].
+        ] ifFalse:[
+            contentsSize := aView widthOfContents.
+            aView transformation notNil ifTrue:[
+                contentsSize := aView transformation applyScaleX:contentsSize.
+            ].
+        ]
     ].
 
     (contentsSize = 0) ifTrue:[
-	percentSize := 100.
-	percentOrigin := 100
+        percentSize := 100.
+        percentOrigin := 100
     ] ifFalse:[
-	(orientation == #vertical) ifTrue:[
-	    viewsSize := aView innerHeight.
-	    contentsPosition := aView yOriginOfContents.
-	] ifFalse:[
-	    viewsSize := aView innerWidth.
-	    contentsPosition := aView xOriginOfContents
-	].
+        (orientation == #vertical) ifTrue:[
+            viewsSize := aView innerHeight.
+            contentsPosition := aView yOriginOfContents.
+        ] ifFalse:[
+            viewsSize := aView innerWidth.
+            contentsPosition := aView xOriginOfContents
+        ].
 
-	percentSize := viewsSize * 100.0 / contentsSize.
-	percentOrigin := contentsPosition * 100.0 / contentsSize.
-	percentOrigin + percentSize > 100.0 ifTrue:[
-	    "actually showing stuff below contents of view"
+        percentSize := viewsSize * 100.0 / contentsSize.
+        percentOrigin := contentsPosition * 100.0 / contentsSize.
+        percentOrigin + percentSize > 100.0 ifTrue:[
+            "actually showing stuff below contents of view"
 "
-	    contentsSize := contentsPosition + aView innerHeight.
-	    percentSize := viewsSize * 100.0 / contentsSize.
-	    percentOrigin := contentsPosition * 100.0 / contentsSize
+            contentsSize := contentsPosition + aView innerHeight.
+            percentSize := viewsSize * 100.0 / contentsSize.
+            percentOrigin := contentsPosition * 100.0 / contentsSize
 "
-	]
+        ]
     ].
     (percentSize = thumbHeight) ifTrue:[
-	self thumbOrigin:percentOrigin
+        self thumbOrigin:percentOrigin
     ] ifFalse:[
-	(percentOrigin = thumbOrigin) ifTrue:[
-	    self thumbHeight:percentSize
-	] ifFalse:[
-	    self thumbOrigin:percentOrigin thumbHeight:percentSize
-	]
+        (percentOrigin = thumbOrigin) ifTrue:[
+            self thumbHeight:percentSize
+        ] ifFalse:[
+            self thumbOrigin:percentOrigin thumbHeight:percentSize
+        ]
     ]
 !
 
@@ -1758,22 +1758,22 @@
     |percent total viewsSize|
 
     (orientation == #vertical) ifTrue:[
-	total := aView heightOfContents.
-	aView transformation notNil ifTrue:[
-	    total := aView transformation applyScaleY:total.
-	].
+        total := aView heightOfContents.
+        aView transformation notNil ifTrue:[
+            total := aView transformation applyScaleY:total.
+        ].
     ] ifFalse:[
-	total := aView widthOfContents.
-	aView transformation notNil ifTrue:[
-	    total := aView transformation applyScaleX:total.
-	].
+        total := aView widthOfContents.
+        aView transformation notNil ifTrue:[
+            total := aView transformation applyScaleX:total.
+        ].
     ].
     (total = 0) ifTrue:[
-	percent := 100
+        percent := 100
     ] ifFalse:[
-	viewsSize := (orientation == #vertical) ifTrue:[aView innerHeight]
-					   ifFalse:[aView innerWidth].
-	percent := viewsSize * 100.0 / total
+        viewsSize := (orientation == #vertical) ifTrue:[aView innerHeight]
+                                           ifFalse:[aView innerWidth].
+        percent := viewsSize * 100.0 / total
     ].
     self thumbHeight:percent
 !
@@ -1784,22 +1784,22 @@
     |percent total contentsPosition|
 
     (orientation == #vertical) ifTrue:[
-	total := aView heightOfContents.
-	aView transformation notNil ifTrue:[
-	    total := aView transformation applyScaleY:total.
-	].
+        total := aView heightOfContents.
+        aView transformation notNil ifTrue:[
+            total := aView transformation applyScaleY:total.
+        ].
     ] ifFalse:[
-	total := aView widthOfContents.
-	aView transformation notNil ifTrue:[
-	    total := aView transformation applyScaleX:total.
-	].
+        total := aView widthOfContents.
+        aView transformation notNil ifTrue:[
+            total := aView transformation applyScaleX:total.
+        ].
     ].
     (total = 0) ifTrue:[
-	percent := 100
+        percent := 100
     ] ifFalse:[
-	contentsPosition := (orientation == #vertical) ifTrue:[aView yOriginOfContents]
-						  ifFalse:[aView xOriginOfContents].
-	percent := contentsPosition * 100.0 / total
+        contentsPosition := (orientation == #vertical) ifTrue:[aView yOriginOfContents]
+                                                  ifFalse:[aView xOriginOfContents].
+        percent := contentsPosition * 100.0 / total
     ].
     self thumbOrigin:percent
 ! !
@@ -1836,5 +1836,5 @@
 !Scroller class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg/Scroller.st,v 1.71 1997-02-08 14:24:23 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg/Scroller.st,v 1.72 1997-02-12 00:24:34 ca Exp $'
 ! !