eliminated accesses to leftOffset
authorClaus Gittinger <cg@exept.de>
Fri, 05 Oct 2001 10:56:34 +0200
changeset 2429 eed79a96e43b
parent 2428 f800d9ec09a8
child 2430 d8f21cf216fb
eliminated accesses to leftOffset
EditField.st
EditTextView.st
ListView.st
MenuView.st
SelectionInListView.st
TextView.st
--- a/EditField.st	Thu Oct 04 19:26:48 2001 +0200
+++ b/EditField.st	Fri Oct 05 10:56:34 2001 +0200
@@ -1205,15 +1205,16 @@
 
     |len s|
 
-    leftOffset := 0.
+    viewOrigin := 0 @ viewOrigin y.
+
     (s := aString) notNil ifTrue:[
-	s := s asString
+        s := s asString
     ].
     self contents:s.
     aBoolean ifTrue:[
-	(len := s size) ~~ 0 ifTrue:[
-	    self selectFromLine:1 col:1 toLine:1 col:len
-	]
+        (len := s size) ~~ 0 ifTrue:[
+            self selectFromLine:1 col:1 toLine:1 col:len
+        ]
     ]
 !
 
@@ -1584,7 +1585,7 @@
     "
      should (& can) we resize ?
     "
-    xCol := (self xOfCol:cursorCol inVisibleLine:cursorLine) - leftOffset.
+    xCol := (self xOfCol:cursorCol inVisibleLine:cursorLine) - viewOrigin x.
     (xCol > (width * (5/6))) ifTrue:[
         self changedPreferredBounds:nil
     ] ifFalse:[
@@ -1605,17 +1606,17 @@
             ].
         ].
 
-        xCol := (self xOfCol:cursorCol inVisibleLine:cursorLine) - leftOffset.
+        xCol := (self xOfCol:cursorCol inVisibleLine:cursorLine) - viewOrigin x.
         (xCol > (width * (5/6))) ifTrue:[
-            newOffset := leftOffset + (width // 2).
+            newOffset := viewOrigin x + (width // 2).
         ] ifFalse:[
             (xCol < (width * (1/6))) ifTrue:[
-                newOffset := 0 max: leftOffset - (width // 2).
+                newOffset := 0 max: viewOrigin x - (width // 2).
             ] ifFalse:[
-                newOffset := leftOffset
+                newOffset := viewOrigin x
             ]
         ].
-        newOffset ~~ leftOffset ifTrue:[
+        newOffset ~~ viewOrigin x ifTrue:[
             self scrollHorizontalTo:newOffset.
         ]
     ].
@@ -1628,7 +1629,7 @@
 
     |xCol|
 
-    leftOffset ~~ 0 ifTrue:[
+    viewOrigin x ~~ 0 ifTrue:[
         xCol := self xOfCol:cursorCol inVisibleLine:cursorLine.
         (xCol < (width * (5/6))) ifTrue:[
             self scrollHorizontalTo:0
@@ -2006,7 +2007,7 @@
 realize
     "scroll back to beginning when realized"
 
-    leftOffset := 0.
+    viewOrigin := 0 @ viewOrigin y.
     super realize
 
     "Created: 24.7.1997 / 18:23:15 / cg"
@@ -2042,14 +2043,10 @@
 
     "/ new:
     "/ care to make the most possible visible
-    leftOffset > 0 ifTrue:[
+    viewOrigin x > 0 ifTrue:[
         wText := self widthOfLine:lineNr.
         wText <= innerWidth ifTrue:[
             self scrollHorizontalTo:0
-"/        ] ifFalse:[
-"/            wText < (leftOffset+self innerWidth) ifTrue:[
-"/                self scrollHorizontalTo:(wText - self innerWidth)
-"/            ]
         ]
     ]
 
@@ -2091,5 +2088,5 @@
 !EditField class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg/EditField.st,v 1.154 2001-10-04 12:58:10 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg/EditField.st,v 1.155 2001-10-05 08:55:40 cg Exp $'
 ! !
--- a/EditTextView.st	Thu Oct 04 19:26:48 2001 +0200
+++ b/EditTextView.st	Fri Oct 05 10:56:34 2001 +0200
@@ -1519,7 +1519,7 @@
                           and:bgColor.
         ^ self
     ].
-    x := (self xOfCol:cursorCol inVisibleLine:cursorVisibleLine) - leftOffset.
+    x := (self xOfCol:cursorCol inVisibleLine:cursorVisibleLine) - viewOrigin x.
     y := self yOfVisibleLine:cursorVisibleLine.
 
     oldPaint := self paint. "/ do not clobber GC
@@ -1809,7 +1809,7 @@
         (line notNil and:[line isText]) ifTrue:[
             cursorCol > 1 ifTrue:[
                 oldClip := self clippingRectangleOrNil.
-                x := (self xOfCol:cursorCol inVisibleLine:cursorVisibleLine) - leftOffset.
+                x := (self xOfCol:cursorCol inVisibleLine:cursorVisibleLine) - viewOrigin x.
                 y := self yOfVisibleLine:cursorVisibleLine.
                 self clippingRectangle:(x@y extent:((font width * 2) @ fontHeight)).
                 super redrawVisibleLine:cursorVisibleLine from:cursorCol-1 to:cursorCol.
@@ -2751,7 +2751,7 @@
             colNr > 1 ifTrue:[
                 cursorVisibleLine notNil ifTrue:[
                     oldClip := self clippingRectangleOrNil.
-                    x := (self xOfCol:colNr inVisibleLine:cursorVisibleLine) - leftOffset.
+                    x := (self xOfCol:colNr inVisibleLine:cursorVisibleLine) - viewOrigin x.
                     y := self yOfVisibleLine:cursorVisibleLine.
                     drawCharacterOnly ifTrue:[
                         self clippingRectangle:(x@y extent:((font width * 2) @ fontHeight)).
@@ -5023,5 +5023,5 @@
 !EditTextView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg/EditTextView.st,v 1.257 2001-10-04 16:53:28 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg/EditTextView.st,v 1.258 2001-10-05 08:55:43 cg Exp $'
 ! !
--- a/ListView.st	Thu Oct 04 19:26:48 2001 +0200
+++ b/ListView.st	Fri Oct 05 10:56:34 2001 +0200
@@ -927,7 +927,7 @@
      (the nonStrings information is remembered to optimize later redraws & height computations)."
 
     |oldFirst oldLeft nonStringsBefore fontHeightBefore
-     scrollToEnd scrollToTop|
+     scrollToEnd scrollToTop newLeftOffset|
 
     scrollToTop := scrollWhenUpdating == #begin or:[scrollWhenUpdating == #beginOfText].
     scrollToEnd := scrollWhenUpdating == #end or:[scrollWhenUpdating == #endOfText].
@@ -936,12 +936,12 @@
         "no contents change"
         scrollToTop ifTrue:[
             self scrollToTop.
-            self scrollToLeft.
         ] ifFalse:[
             scrollToEnd ifTrue:[
                 self scrollToBottom.
             ]
         ].
+        self scrollToLeft.
         ^ self
     ].
     list := aCollection.
@@ -967,20 +967,30 @@
 
     widthOfWidestLine := nil.   "/ i.e. unknown
     oldFirst := firstLineShown.
-    oldLeft := leftOffset.
+    oldLeft := viewOrigin x.
 
     (includesNonStrings ~~ nonStringsBefore) ifTrue:[
         self computeNumberOfLinesShown.
     ].
+
+    newLeftOffset := viewOrigin x.
     scrollToTop ifTrue:[
         firstLineShown := 1.
-        leftOffset := 0.
+        newLeftOffset := 0.
     ] ifFalse:[
         scrollToEnd ifTrue:[
             firstLineShown := (list size - nFullLinesShown + 1) max:1.
-            leftOffset := 0.
+            newLeftOffset := 0.
         ]
     ].
+    newLeftOffset > 0 ifTrue:[
+        self widthOfContents <= self innerWidth ifTrue:[
+            newLeftOffset := 0.
+        ].
+    ].
+    newLeftOffset ~= oldLeft ifTrue:[ 
+        viewOrigin := newLeftOffset @ viewOrigin y.
+    ].
 
     realized ifTrue:[
         self contentsChanged.
@@ -1164,8 +1174,8 @@
     |oldFirst nonStringsBefore linesShownBefore|
 
     (aCollection isNil and:[list isNil]) ifTrue:[
-	"no change"
-	^ self
+        "no change"
+        ^ self
     ].
 
 "/    list isNil ifTrue:[
@@ -1181,42 +1191,41 @@
     includesNonStrings := false.
 
     list notNil ifTrue:[
-	expandTabs ifTrue:[
-	    self expandTabs
-	] ifFalse:[
-	    includesNonStrings := (list findFirst:[:e | e isString not]) ~~ 0.
-	].
+        expandTabs ifTrue:[
+            self expandTabs
+        ] ifFalse:[
+            includesNonStrings := (list findFirst:[:e | e isString not]) ~~ 0.
+        ].
     ].
     (includesNonStrings ~~ nonStringsBefore) ifTrue:[
-	self getFontParameters.
-	self computeNumberOfLinesShown.
+        self getFontParameters.
+        self computeNumberOfLinesShown.
     ].
 
 "/ new - reposition horizontally if too big
     widthOfWidestLine := nil.   "/ i.e. unknown
     innerWidth >= self widthOfContents ifTrue:[
-	viewOrigin x:0.
-	leftOffset := 0.
+        viewOrigin := 0 @ viewOrigin y.
     ].
     self contentsChanged.
 
 "/ new - reposition vertically if too big
     (firstLineShown + nFullLinesShown) > self size ifTrue:[
-	oldFirst := firstLineShown.
-	firstLineShown := self size - nFullLinesShown + 1.
-	firstLineShown < 1 ifTrue:[firstLineShown := 1].
-
-	viewOrigin y:(firstLineShown - 1 * fontHeight).
-	self originChanged:0 @ ((oldFirst - 1) negated * fontHeight).
-	linesShownBefore := nil.
-	shown ifTrue:[
-	    self clear.
-	]
+        oldFirst := firstLineShown.
+        firstLineShown := self size - nFullLinesShown + 1.
+        firstLineShown < 1 ifTrue:[firstLineShown := 1].
+
+        viewOrigin y:(firstLineShown - 1 * fontHeight).
+        self originChanged:0 @ ((oldFirst - 1) negated * fontHeight).
+        linesShownBefore := nil.
+        shown ifTrue:[
+            self clear.
+        ]
     ].
 "/ end new
 
     (shown and:[doRedraw]) ifTrue:[
-	  self redrawFromVisibleLine:1 to:nLinesShown
+          self redrawFromVisibleLine:1 to:nLinesShown
 
 "/        linesShownBefore isNil ifTrue:[
 "/            self redrawFromVisibleLine:1 to:nLinesShown
@@ -1543,7 +1552,7 @@
     ].
 
     (startLine <= e) ifTrue:[
-        x := textStartLeft - leftOffset.
+        x := textStartLeft - viewOrigin x.
         self paint:fg on:bg.
         self from:startLine to:e do:[:line |
             line notNil ifTrue:[
@@ -1613,7 +1622,7 @@
 drawLine:line inVisible:visLineNr with:fg and:bg
     "draw a given string at visible lines position in fg/bg"
 
-    self drawLine:line atX:(textStartLeft - leftOffset) inVisible:visLineNr with:fg and:bg
+    self drawLine:line atX:(textStartLeft - viewOrigin x) inVisible:visLineNr with:fg and:bg
 !
 
 drawVisibleLine:visLineNr col:col with:fg and:bg
@@ -1626,7 +1635,7 @@
         ^ self drawVisibleLine:visLineNr with:fg and:bg
     ].
 
-    x := (self xOfCol:col inVisibleLine:visLineNr) - leftOffset.
+    x := (self xOfCol:col inVisibleLine:visLineNr) - viewOrigin x.
     y := self yOfVisibleLine:visLineNr.
     self paint:bg.
 
@@ -1666,7 +1675,7 @@
         ifTrue:[
             self drawVisibleLine:visLineNr with:fg and:bg.
         ] ifFalse:[
-            x := (self xOfCol:sCol inVisibleLine:visLineNr) - leftOffset.
+            x := (self xOfCol:sCol inVisibleLine:visLineNr) - viewOrigin x.
             y := (self yOfVisibleLine:visLineNr).
             yf := y - (lineSpacing // 2).
             len := lineString size.
@@ -1729,11 +1738,11 @@
         index1 := startCol
     ].
     y := self yOfVisibleLine:visLineNr.
-    x := (self xOfCol:index1 inVisibleLine:visLineNr) - leftOffset.
+    x := (self xOfCol:index1 inVisibleLine:visLineNr) - viewOrigin x.
     backgroundAlreadyClearedColor == bg ifFalse:[
         self paint:bg.
         self fillRectangleX:x y:y - (lineSpacing // 2)
-                      width:(width + leftOffset - x)
+                      width:(width + viewOrigin x - x)
                      height:fontHeight.
     ].
     lineString := self visibleAt:visLineNr.
@@ -1758,11 +1767,11 @@
     "draw a visible line in fg/bg"
 
     self 
-	drawLine:(self visibleAt:visLineNr) 
-	atX:(textStartLeft - leftOffset) 
-	inVisible:visLineNr 
-	with:fg 
-	and:bg
+        drawLine:(self visibleAt:visLineNr) 
+        atX:(textStartLeft - viewOrigin x) 
+        inVisible:visLineNr 
+        with:fg 
+        and:bg
 
     "Modified: 28.2.1996 / 19:30:23 / cg"
 !
@@ -2039,7 +2048,6 @@
     firstLineShown := 1.
     nFullLinesShown := 1. "just any value ..."
     nLinesShown := 1.     "just any value"
-    leftOffset := 0.
     partialLines := true.
     tabPositions := UserDefaultTabPositions ? DefaultTabPositions.
     includesNonStrings := false.
@@ -2175,7 +2183,7 @@
     |lineString linePixelWidth xRel runCol posLeft posRight done
      hasEmphasis oPosRight oPosLeft|
 
-    xRel := x - textStartLeft + leftOffset.
+    xRel := x - textStartLeft + viewOrigin x.
     (xRel <= 0) ifTrue:[^ 1].
 
     lineString := self visibleAt:visLineNr.
@@ -2264,7 +2272,7 @@
         ]
     ].
 "/self paint:Color red.
-"/self displayRectangleX:posLeft+textStartLeft-leftOffset y:(self yOfVisibleLine:visLineNr)
+"/self displayRectangleX:posLeft+textStartLeft-viewOrigin x y:(self yOfVisibleLine:visLineNr)
 "/                       width:(posRight-posLeft) height:fontHeight.
 "/self paint:Color black.
     ^ runCol
@@ -3079,7 +3087,7 @@
     "return the horizontal origin of the contents in pixels
      - used for scrollbar interface"
 
-    ^ leftOffset 
+    ^ viewOrigin x 
 !
 
 yOriginOfContents
@@ -3303,7 +3311,7 @@
     visLnr isNil ifTrue:[^ self].
 
     xWant := self xOfCol:aCol inVisibleLine:visLnr.
-    xVis := xWant - leftOffset.
+    xVis := xWant - viewOrigin x.
 
     "
      dont scroll, if already visible
@@ -3466,7 +3474,7 @@
 
     |nPixel|
 
-    nPixel := aPixelOffset - leftOffset.
+    nPixel := aPixelOffset - viewOrigin x.
     nPixel ~~ 0 ifTrue:[
         self scrollTo:(viewOrigin + (nPixel @ 0)) redraw:true
     ]
@@ -3518,31 +3526,33 @@
 scrollToCol:aColNr
     "change origin to make aColNr be the left col"
 
-    |pxlOffset|
+    |pxlOffset leftOffset|
+
+    leftOffset := viewOrigin x.
 
     aColNr == 1 ifTrue:[
-	leftOffset ~~ 0 ifTrue:[
-	    self scrollLeft:leftOffset.
-	].
-	^ self
+        leftOffset ~~ 0 ifTrue:[
+            self scrollLeft:leftOffset.
+        ].
+        ^ self
     ].
 
     pxlOffset := font width * (aColNr - 1).
 
     pxlOffset < leftOffset ifTrue:[
-	self scrollLeft:(leftOffset - pxlOffset)
+        self scrollLeft:(leftOffset - pxlOffset)
     ] ifFalse:[
-	pxlOffset > leftOffset ifTrue:[
-	    self scrollRight:(pxlOffset - leftOffset)
-	]
+        pxlOffset > leftOffset ifTrue:[
+            self scrollRight:(pxlOffset - leftOffset)
+        ]
     ]
 !
 
 scrollToLeft
     "change origin to start (left) of text"
 
-    leftOffset ~~ 0 ifTrue:[
-	self scrollToCol:1
+    viewOrigin x ~~ 0 ifTrue:[
+        self scrollToCol:1
     ]
 !
 
@@ -3747,7 +3757,7 @@
      y1   "{ Class:SmallInteger }"
      y    "{ Class:SmallInteger }"
      x    "{ Class:SmallInteger }"
-     delta newFirstLine newViewOrigin newLeftOffset
+     delta newFirstLine newViewOrigin 
      hBefore wBefore inv wg|
 
     hBefore := height.
@@ -3758,16 +3768,16 @@
 "/  compute valid horizontal offset x
 
     (x := dltOrg x) ~~ 0 ifTrue:[
-        tmp := leftOffset + x.
+        tmp := viewOrigin x + x.
 
         x < 0 ifTrue:[                                          "/ scrolling left
-            tmp < 0 ifTrue:[x := 0 - leftOffset]
+            tmp < 0 ifTrue:[x := 0 - viewOrigin x]
         ] ifFalse:[                                             "/ scrolling right
          "/ allows scrolling to the right of widest line
             max := self widthOfContents + (self additionalMarginForHorizontalScroll).
 
             tmp + width > max ifTrue:[
-                x := (max - leftOffset - width) max:0
+                x := (max - viewOrigin x - width) max:0
             ]
         ]
     ].
@@ -3800,13 +3810,11 @@
 
     newFirstLine := firstLineShown + noLn.
     newViewOrigin := viewOrigin + delta.
-    newLeftOffset := newViewOrigin x max:0.
 
     (shown and:[doRedraw]) ifFalse:[
         self originWillChange.
         firstLineShown := newFirstLine.
         viewOrigin := newViewOrigin.
-        leftOffset := newLeftOffset.
         ^ self originChanged:delta
     ].
 
@@ -3823,7 +3831,6 @@
         self originWillChange.
         firstLineShown := newFirstLine.
         viewOrigin := newViewOrigin.
-        leftOffset := newLeftOffset.
         self invalidate.
         ^ self originChanged:delta
     ].
@@ -3897,7 +3904,6 @@
 
     firstLineShown := newFirstLine.
     viewOrigin := newViewOrigin.
-    leftOffset := newLeftOffset.
 
     self invalidateDeviceRectangle:inv repairNow:false.
 
@@ -4388,5 +4394,5 @@
 !ListView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg/ListView.st,v 1.256 2001-10-04 16:53:32 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg/ListView.st,v 1.257 2001-10-05 08:55:19 cg Exp $'
 ! !
--- a/MenuView.st	Thu Oct 04 19:26:48 2001 +0200
+++ b/MenuView.st	Fri Oct 05 10:56:34 2001 +0200
@@ -1418,7 +1418,7 @@
 
     markType := line at:i2.
 
-    x := (self xOfCol:markIndex inVisibleLine:visLineNr) - leftOffset.
+    x := (self xOfCol:markIndex inVisibleLine:visLineNr) - viewOrigin x.
     y := (self yOfVisibleLine:visLineNr) - (lineSpacing//2).
 
     self paint:bg.
@@ -2734,5 +2734,5 @@
 !MenuView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg/MenuView.st,v 1.129 2001-09-05 14:33:38 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg/MenuView.st,v 1.130 2001-10-05 08:56:34 cg Exp $'
 ! !
--- a/SelectionInListView.st	Thu Oct 04 19:26:48 2001 +0200
+++ b/SelectionInListView.st	Fri Oct 05 10:56:34 2001 +0200
@@ -2130,7 +2130,7 @@
                 t emphasisAllRemove:#color.
                 self
                     drawLine:t 
-                    atX:(textStartLeft - leftOffset) 
+                    atX:(textStartLeft - viewOrigin x) 
                     inVisible:visLineNr 
                     with:fg 
                     and:bg
@@ -2143,7 +2143,7 @@
                     t := LabelAndIcon icon:item icon string:t.
                     self
                         drawLine:t 
-                        atX:(textStartLeft - leftOffset) 
+                        atX:(textStartLeft - viewOrigin x) 
                         inVisible:visLineNr 
                         with:fg 
                         and:bg
@@ -2188,8 +2188,8 @@
             includesNonStrings ifFalse:[
                 wEdge := wEdge max:(self widthOfContents).
             ].
-            self drawEdgesForX:(margin - leftOffset) y:y 
-                         width:wEdge+leftOffset height:fontHeight 
+            self drawEdgesForX:(margin - viewOrigin x) y:y 
+                         width:wEdge+viewOrigin x height:fontHeight 
                          level:hilightLevel.
 
 
@@ -4022,5 +4022,5 @@
 !SelectionInListView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg/SelectionInListView.st,v 1.195 2001-09-28 13:25:26 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg/SelectionInListView.st,v 1.196 2001-10-05 08:56:24 cg Exp $'
 ! !
--- a/TextView.st	Thu Oct 04 19:26:48 2001 +0200
+++ b/TextView.st	Fri Oct 05 10:56:34 2001 +0200
@@ -834,7 +834,7 @@
         self startAutoScrollDown:(y - height).
         ^ self
     ].
-    ((x < 0) and:[leftOffset ~~ 0]) ifTrue:[
+    ((x < 0) and:[viewOrigin x ~~ 0]) ifTrue:[
         self compressMotionEvents:false.
         self startAutoScrollLeft:x.
         ^ self
@@ -1149,7 +1149,7 @@
                               |prevLine prevCol moveBack pos1|
 
                               prevLine := firstLineShown.
-                              prevCol := leftOffset.
+                              prevCol := viewOrigin x.
                               self selectFromLine:selectionStartLine col:selectionStartCol
                                            toLine:line col:col.
 
@@ -1160,7 +1160,7 @@
 
                                       moveBack := false.
                                       (')]}>' includes:ch) ifTrue:[
-                                           (firstLineShown ~~ prevLine or:[prevCol ~~ leftOffset]) ifTrue:[
+                                           (firstLineShown ~~ prevLine or:[prevCol ~~ viewOrigin x]) ifTrue:[
                                                moveBack := true
                                            ] 
                                       ] ifFalse:[
@@ -2035,62 +2035,62 @@
     |len line l|
 
     selectionStartLine notNil ifTrue:[
-	line := self visibleLineToAbsoluteLine:visLine.
-	(line between:selectionStartLine and:selectionEndLine) ifTrue:[
-	    (line == selectionStartLine) ifTrue:[
-		(line == selectionEndLine) ifTrue:[
-		    "its part-of-single-line selection"
-		    self clearMarginOfVisibleLine:visLine with:bgColor.
-		    (selectionStartCol > 1) ifTrue:[
-			super redrawVisibleLine:visLine
-					   from:1
-					     to:(selectionStartCol - 1)
-		    ].
-		    self drawVisibleLine:visLine from:selectionStartCol
-						   to:selectionEndCol
-						 with:selectionFgColor
-						  and:selectionBgColor.
-		    super redrawVisibleLine:visLine
-				       from:(selectionEndCol + 1).
-		    ^ self
-		].
-
-		"its the first line of a multi-line selection"
-		(selectionStartCol ~~ 1) ifTrue:[
-		    self clearMarginOfVisibleLine:visLine with:bgColor.
-		    super redrawVisibleLine:visLine
-				       from:1
-					 to:(selectionStartCol - 1)
-		] ifFalse:[
-		    leftOffset == 0 ifTrue:[
-			self clearMarginOfVisibleLine:visLine with:selectionBgColor.
-		    ]
-		].
-		self drawVisibleLine:visLine from:selectionStartCol
-				with:selectionFgColor and:selectionBgColor.
-		^ self
-	    ].
-
-	    (line == selectionEndLine) ifTrue:[
-		"its the last line of a multi-line selection"
-		(selectionEndCol == 0) ifTrue:[
-		    ^ super redrawVisibleLine:visLine
-		].
-		l := self visibleAt:selectionEndLine.
-		len := l size.
-
-		self clearMarginOfVisibleLine:visLine with:selectionBgColor.
-		self drawVisibleLine:visLine from:1 to:selectionEndCol
-				with:selectionFgColor and:selectionBgColor.
-		super redrawVisibleLine:visLine from:(selectionEndCol + 1).
-		^ self
-	    ].
-
-	    "its a full line in a multi-line selection"
-	    self clearMarginOfVisibleLine:visLine with:selectionBgColor.
-	    self drawVisibleLine:visLine with:selectionFgColor and:selectionBgColor.
-	    ^ self
-	]
+        line := self visibleLineToAbsoluteLine:visLine.
+        (line between:selectionStartLine and:selectionEndLine) ifTrue:[
+            (line == selectionStartLine) ifTrue:[
+                (line == selectionEndLine) ifTrue:[
+                    "its part-of-single-line selection"
+                    self clearMarginOfVisibleLine:visLine with:bgColor.
+                    (selectionStartCol > 1) ifTrue:[
+                        super redrawVisibleLine:visLine
+                                           from:1
+                                             to:(selectionStartCol - 1)
+                    ].
+                    self drawVisibleLine:visLine from:selectionStartCol
+                                                   to:selectionEndCol
+                                                 with:selectionFgColor
+                                                  and:selectionBgColor.
+                    super redrawVisibleLine:visLine
+                                       from:(selectionEndCol + 1).
+                    ^ self
+                ].
+
+                "its the first line of a multi-line selection"
+                (selectionStartCol ~~ 1) ifTrue:[
+                    self clearMarginOfVisibleLine:visLine with:bgColor.
+                    super redrawVisibleLine:visLine
+                                       from:1
+                                         to:(selectionStartCol - 1)
+                ] ifFalse:[
+                    viewOrigin x == 0 ifTrue:[
+                        self clearMarginOfVisibleLine:visLine with:selectionBgColor.
+                    ]
+                ].
+                self drawVisibleLine:visLine from:selectionStartCol
+                                with:selectionFgColor and:selectionBgColor.
+                ^ self
+            ].
+
+            (line == selectionEndLine) ifTrue:[
+                "its the last line of a multi-line selection"
+                (selectionEndCol == 0) ifTrue:[
+                    ^ super redrawVisibleLine:visLine
+                ].
+                l := self visibleAt:selectionEndLine.
+                len := l size.
+
+                self clearMarginOfVisibleLine:visLine with:selectionBgColor.
+                self drawVisibleLine:visLine from:1 to:selectionEndCol
+                                with:selectionFgColor and:selectionBgColor.
+                super redrawVisibleLine:visLine from:(selectionEndCol + 1).
+                ^ self
+            ].
+
+            "its a full line in a multi-line selection"
+            self clearMarginOfVisibleLine:visLine with:selectionBgColor.
+            self drawVisibleLine:visLine with:selectionFgColor and:selectionBgColor.
+            ^ self
+        ]
     ].
     super redrawVisibleLine:visLine
 
@@ -3224,5 +3224,5 @@
 !TextView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg/TextView.st,v 1.171 2001-10-02 18:03:26 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg/TextView.st,v 1.172 2001-10-05 08:56:11 cg Exp $'
 ! !