ListView.st
changeset 2561 b4b64dd40018
parent 2559 a2c72ee75373
child 2562 bf1ac08c9de5
--- a/ListView.st	Tue Jul 23 21:45:48 2002 +0200
+++ b/ListView.st	Tue Jul 23 22:51:52 2002 +0200
@@ -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
@@ -13,17 +13,17 @@
 "{ Package: 'stx:libwidg' }"
 
 View subclass:#ListView
-        instanceVariableNames:'list firstLineShown nFullLinesShown nLinesShown fgColor bgColor
-                partialLines leftMargin topMargin textStartLeft textStartTop
-                innerWidth tabPositions lineSpacing fontHeight fontAscent
-                fontIsFixedWidth fontWidth autoScroll autoScrollBlock
-                autoScrollDeltaT wordCheck includesNonStrings widthOfWidestLine
-                listMsg viewOrigin listChannel backgroundAlreadyClearedColor
-                scrollWhenUpdating'
-        classVariableNames:'DefaultForegroundColor DefaultBackgroundColor DefaultTabPositions
-                UserDefaultTabPositions DefaultLeftMargin DefaultTopMargin'
-        poolDictionaries:''
-        category:'Views-Text'
+	instanceVariableNames:'list firstLineShown nFullLinesShown nLinesShown fgColor bgColor
+		partialLines leftMargin topMargin textStartLeft textStartTop
+		innerWidth tabPositions lineSpacing fontHeight fontAscent
+		fontIsFixedWidth fontWidth autoScroll autoScrollBlock
+		autoScrollDeltaT wordCheck includesNonStrings widthOfWidestLine
+		listMsg viewOrigin listChannel backgroundAlreadyClearedColor
+		scrollWhenUpdating'
+	classVariableNames:'DefaultForegroundColor DefaultBackgroundColor DefaultTabPositions
+		UserDefaultTabPositions DefaultLeftMargin DefaultTopMargin'
+	poolDictionaries:''
+	category:'Views-Text'
 !
 
 !ListView class methodsFor:'documentation'!
@@ -31,7 +31,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
@@ -98,15 +98,15 @@
     [Instance variables:]
 
       list                <aCollection>           the text strings, a collection of lines.
-                                                  Nils may be used for empty lines.
+						  Nils may be used for empty lines.
 
       firstLineShown      <Number>                the index of the 1st visible line (1 ..)
       leftOffset          <Number>                left offset for horizontal scroll
 
       nFullLinesShown     <Number>                the number of unclipped lines in visible area
-                                                  (internal; updated on size changes)
+						  (internal; updated on size changes)
       nLinesShown         <Number>                the number of lines in visible area, incl. partial
-                                                  (internal; updated on size changes)
+						  (internal; updated on size changes)
 
       fgColor             <Color>                 color to draw characters
       bgColor             <Color>                 the background
@@ -124,39 +124,39 @@
       fontWidth           <Number>                width of space (internal)
       lineSpacing         <Number>                pixels between lines
       lastSearchPattern   <String>                last pattern for searching 
-                                                  (kept to provide a default for next search)
+						  (kept to provide a default for next search)
       lastSearchIgnoredCase   <Boolean>           last search ignored case
-                                                  (kept to provide a default for next search)
+						  (kept to provide a default for next search)
       wordCheck           <Block>                 rule used for check for word boundaries in word select
-                                                  The default rule is to return true for alphaNumeric characters.
-                                                  (can be changed to allow for underscore and other
-                                                   characters to be treated as alphaCharacters)
+						  The default rule is to return true for alphaNumeric characters.
+						  (can be changed to allow for underscore and other
+						   characters to be treated as alphaCharacters)
 
       autoScrollBlock     <Block>                 block installed as timeoutBlock when doing an
-                                                  autoScroll (internal)
+						  autoScroll (internal)
       autoScrollDeltaT                            computed scroll time delta in seconds (internal)
 
       includesNonStrings                          cached flag if any non-strings are in list
       widthOfWidestLine                           cached width of widest line
       listMsg                                     if view has a model and listMsg is non-nil,
-                                                  this is sent to the model to aquired a new contents
-                                                  whenever a change of the aspect  (aspectMsg) occurs.
+						  this is sent to the model to aquired a new contents
+						  whenever a change of the aspect  (aspectMsg) occurs.
 
       viewOrigin                                  the current origin 
 
       backgroundAlreadyClearedColor               internal; speedup by avoiding
-                                                  multiple fills when drawing
-                                                  internal lines
+						  multiple fills when drawing
+						  internal lines
 
       scrollWhenUpdating
-                                <Symbol>        defines how the view is scrolled if the
-                                                model changes its value by some outside activity
-                                                (i.e. not by user input).
-                                                Can be one of:
-                                                    #keep / nil     -> stay unchanged
-                                                    #endOfText      -> scroll to the end
-                                                    #beginOfText    -> scroll to the top
-                                                The default is #beginOfText (i.e. scroll to top).
+				<Symbol>        defines how the view is scrolled if the
+						model changes its value by some outside activity
+						(i.e. not by user input).
+						Can be one of:
+						    #keep / nil     -> stay unchanged
+						    #endOfText      -> scroll to the end
+						    #beginOfText    -> scroll to the top
+						The default is #beginOfText (i.e. scroll to top).
 
     [StyleSheet parameters:]
 
@@ -166,10 +166,10 @@
       textTabPositions                            defaults to #(1 9 17 25 ...)
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 
     [see also:]
-        TextView EditTextView
+	TextView EditTextView
         
 "
 !
@@ -182,151 +182,151 @@
     anyway, here are a few examples:
 
      basic simple setup:
-                                                                        [exBegin]
-        |top l|
-
-        top := StandardSystemView new.
-        top extent:100@200.
-
-        l := ListView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
-        l list:#('one' 'two' 'three').
-
-        top open
-                                                                        [exEnd]
+									[exBegin]
+	|top l|
+
+	top := StandardSystemView new.
+	top extent:100@200.
+
+	l := ListView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
+	l list:#('one' 'two' 'three').
+
+	top open
+									[exEnd]
 
 
 
       specifying textMargins (these have NOTHING to do with the viewInset):
-                                                                        [exBegin]
-        |top l|
-
-        top := StandardSystemView new.
-        top extent:100@200.
-
-        l := ListView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
-        l list:#('one' 'two' 'three').
-        l topMargin:10.
-        l leftMargin:20.
-
-        top open
-                                                                        [exEnd]
+									[exBegin]
+	|top l|
+
+	top := StandardSystemView new.
+	top extent:100@200.
+
+	l := ListView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
+	l list:#('one' 'two' 'three').
+	l topMargin:10.
+	l leftMargin:20.
+
+	top open
+									[exEnd]
 
 
 
       globally set the fg/bg colors:
-                                                                        [exBegin]
-        |top l|
-
-        top := StandardSystemView new.
-        top extent:100@200.
-
-        l := ListView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
-        l list:#('one' 'two' 'three').
-        l foregroundColor:(Color white).
-        l backgroundColor:(Color blue).
-
-        top open
-                                                                        [exEnd]
+									[exBegin]
+	|top l|
+
+	top := StandardSystemView new.
+	top extent:100@200.
+
+	l := ListView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
+	l list:#('one' 'two' 'three').
+	l foregroundColor:(Color white).
+	l backgroundColor:(Color blue).
+
+	top open
+									[exEnd]
 
 
 
       non-string (text) entries:
-                                                                        [exBegin]
-        |top list l|
-
-        top := StandardSystemView new.
-        top extent:100@200.
-
-        l := ListView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
-        list := #('all' 'of' 'your' 'preferred' 'colors') 
-                with:#(red green blue 'orange' cyan)
-                collect:[:s :clr | 
-                            Text string:s 
-                                 emphasis:(Array with:#bold
-                                                 with:(#color->(Color name:clr))) ].
-        l list:list.
-
-        top open
-                                                                        [exEnd]
+									[exBegin]
+	|top list l|
+
+	top := StandardSystemView new.
+	top extent:100@200.
+
+	l := ListView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
+	list := #('all' 'of' 'your' 'preferred' 'colors') 
+		with:#(red green blue 'orange' cyan)
+		collect:[:s :clr | 
+			    Text string:s 
+				 emphasis:(Array with:#bold
+						 with:(#color->(Color name:clr))) ].
+	l list:list.
+
+	top open
+									[exEnd]
 
 
 
       generic non-string entries:
       (notice: ColoredListEntry is obsoleted by Text)
-                                                                        [exBegin]
-        |top list l|
-
-        top := StandardSystemView new.
-        top extent:100@200.
-
-        l := ListView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
-        list := #('all' 'of' 'your' 'preferred' 'colors') 
-                with:#(red green blue 'orange' cyan)
-                collect:[:s :clr | ColoredListEntry string:s color:(Color name:clr) ].
-        l list:list.
-
-        top open
-                                                                        [exEnd]
+									[exBegin]
+	|top list l|
+
+	top := StandardSystemView new.
+	top extent:100@200.
+
+	l := ListView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
+	list := #('all' 'of' 'your' 'preferred' 'colors') 
+		with:#(red green blue 'orange' cyan)
+		collect:[:s :clr | ColoredListEntry string:s color:(Color name:clr) ].
+	l list:list.
+
+	top open
+									[exEnd]
 
 
 
       using a model (default listMessage is aspectMessage):
-                                                                        [exBegin]
-        |top model l theModelsText|
-
-        model := Plug new.
-        model respondTo:#modelsAspect
-                   with:[ theModelsText ].
-
-        top := StandardSystemView new.
-        top extent:100@200.
-
-        l := ListView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
-        l model:model.
-        l aspect:#modelsAspect.
-
-        top open.
-
-        Delay waitForSeconds:3.
-        theModelsText := #('foo' 'bar' 'baz').
-        model changed:#modelsAspect.
-                                                                        [exEnd]
+									[exBegin]
+	|top model l theModelsText|
+
+	model := Plug new.
+	model respondTo:#modelsAspect
+		   with:[ theModelsText ].
+
+	top := StandardSystemView new.
+	top extent:100@200.
+
+	l := ListView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
+	l model:model.
+	l aspect:#modelsAspect.
+
+	top open.
+
+	Delay waitForSeconds:3.
+	theModelsText := #('foo' 'bar' 'baz').
+	model changed:#modelsAspect.
+									[exEnd]
 
 
 
       using a model with different aspects
       for two listViews:
-                                                                        [exBegin]
-        |top model l1 l2 plainText|
-
-        plainText := #('').
-
-        model := Plug new.
-        model respondTo:#modelsUppercaseText
-                   with:[ plainText asStringCollection 
-                              collect:[:l | l asUppercase]].
-        model respondTo:#modelsLowercaseText
-                   with:[ plainText asStringCollection 
-                              collect:[:l | l asLowercase]].
-
-        top := StandardSystemView extent:200@200.
-
-        l1 := ListView origin:0.0 @ 0.0 corner:1.0 @ 0.5 in:top.
-        l1 model:model.
-        l1 aspect:#modelsAspect.
-        l1 listMessage:#modelsUppercaseText.
-
-        l2 := ListView origin:0.0 @ 0.5 corner:1.0 @ 1.0 in:top.
-        l2 model:model.
-        l2 aspect:#modelsAspect.
-        l2 listMessage:#modelsLowercaseText.
-
-        top open.
-
-        Delay waitForSeconds:3.
-        plainText := #('foo' 'bar' 'baz').
-        model changed:#modelsAspect.
-                                                                        [exEnd]
+									[exBegin]
+	|top model l1 l2 plainText|
+
+	plainText := #('').
+
+	model := Plug new.
+	model respondTo:#modelsUppercaseText
+		   with:[ plainText asStringCollection 
+			      collect:[:l | l asUppercase]].
+	model respondTo:#modelsLowercaseText
+		   with:[ plainText asStringCollection 
+			      collect:[:l | l asLowercase]].
+
+	top := StandardSystemView extent:200@200.
+
+	l1 := ListView origin:0.0 @ 0.0 corner:1.0 @ 0.5 in:top.
+	l1 model:model.
+	l1 aspect:#modelsAspect.
+	l1 listMessage:#modelsUppercaseText.
+
+	l2 := ListView origin:0.0 @ 0.5 corner:1.0 @ 1.0 in:top.
+	l2 model:model.
+	l2 aspect:#modelsAspect.
+	l2 listMessage:#modelsLowercaseText.
+
+	top open.
+
+	Delay waitForSeconds:3.
+	plainText := #('foo' 'bar' 'baz').
+	model changed:#modelsAspect.
+									[exEnd]
 
 "
 ! !
@@ -353,7 +353,7 @@
     "return an array containing tab positions for 4-col tabs"
 
     ^ #(1 5 9 13 17 21 25 29 33 37 41 45 49 53 57 61 65 69 73 77 81 
-        85 89 93 97 101 105 109 113 114 121 125 129 133 137 141 145)
+	85 89 93 97 101 105 109 113 114 121 125 129 133 137 141 145)
 !
 
 tab8Positions
@@ -366,8 +366,8 @@
     "extract values from the styleSheet and cache them in class variables"
 
     <resource: #style (#'text.foregroundColor' #'text.backgroundColor'
-                       #'text.tabPositions'
-                       #'text.font')>
+		       #'text.tabPositions'
+		       #'text.font')>
 
     DefaultForegroundColor := StyleSheet colorAt:'text.foregroundColor' default:Black.
     DefaultBackgroundColor := StyleSheet colorAt:'text.backgroundColor' default:White.
@@ -426,9 +426,9 @@
     "return the scroll behavior, when I get a new text 
      (via the model or the #contents/#list)
      Possible returnValues are:
-        #keep / nil     -> no change
-        #endOfText      -> scroll to the end
-        #beginOfText    -> scroll to the top
+	#keep / nil     -> no change
+	#endOfText      -> scroll to the end
+	#beginOfText    -> scroll to the top
      The default is #beginOfText.
      This may be useful for fields which get new values assigned from
      the program (i.e. not from the user)"
@@ -440,9 +440,9 @@
     "define how to scroll, when I get a new text 
      (via the model or the #contents/#list)
      Allowed arguments are:
-        #keep / nil     -> no change
-        #endOfText      -> scroll to the end
-        #beginOfText    -> scroll to the top
+	#keep / nil     -> no change
+	#endOfText      -> scroll to the end
+	#beginOfText    -> scroll to the top
      The default is #beginOfText.
      This may be useful for fields which get new values assigned from
      the program (i.e. not from the user)"
@@ -460,22 +460,22 @@
     list add:aString.
 
     includesNonStrings ifFalse:[
-        includesNonStrings := (aString notNil and:[aString isString not]).
-        includesNonStrings ifTrue:[
-            fontHeightBefore := fontHeight.
-            self getFontParameters.
-            fontHeightBefore ~~ fontHeight ifTrue:[
-                self invalidate
-            ].
-        ].
+	includesNonStrings := (aString notNil and:[aString isString not]).
+	includesNonStrings ifTrue:[
+	    fontHeightBefore := fontHeight.
+	    self getFontParameters.
+	    fontHeightBefore ~~ fontHeight ifTrue:[
+		self invalidate
+	    ].
+	].
     ].
 
     widthOfWidestLine notNil ifTrue:[
-        self recomputeWidthOfWidestLineFor:aString
+	self recomputeWidthOfWidestLineFor:aString
     ].
 
     shown ifTrue:[
-        self redrawLine:(self size).
+	self redrawLine:(self size).
     ].
     self contentsChanged.             "recompute scrollbars"
 
@@ -491,29 +491,29 @@
     list add:aString beforeIndex:index.
 
     widthOfWidestLine notNil ifTrue:[
-        self recomputeWidthOfWidestLineFor:aString
+	self recomputeWidthOfWidestLineFor:aString
     ].
 
     includesNonStrings ifFalse:[
-        includesNonStrings := (aString notNil and:[aString isString not]).
+	includesNonStrings := (aString notNil and:[aString isString not]).
 "/        includesNonStrings ifTrue:[self getFontParameters].
     ].
     shown ifTrue:[
-        lastShown := self lastLineShown.
-        index <= 2 ifTrue:[
-            self invalidate
-        ] ifFalse:[
-            index to:lastShown do:[:eachLine |
-                self invalidateLine:eachLine
-            ].
-        ].
+	lastShown := self lastLineShown.
+	index <= 2 ifTrue:[
+	    self invalidate
+	] ifFalse:[
+	    index to:lastShown do:[:eachLine |
+		self invalidateLine:eachLine
+	    ].
+	].
     ].
     self contentsChanged.             "recompute scrollbars"
 
     (scrollWhenUpdating == #end or:[scrollWhenUpdating == #endOfText]) ifTrue:[
-        "/ self selection isNil ifTrue:[
-            self scrollToBottom.
-        "/ ]
+	"/ self selection isNil ifTrue:[
+	    self scrollToBottom.
+	"/ ]
     ].
 !
 
@@ -524,36 +524,36 @@
 
     list isNil ifTrue:[list := OrderedCollection new].
     aCollectionOfLines do:[:eachLine |
-        list addAll:aCollectionOfLines beforeIndex:index.
+	list addAll:aCollectionOfLines beforeIndex:index.
     ].
     includesNonStrings ifFalse:[
-        aCollectionOfLines do:[:eachLine |
-            includesNonStrings := includesNonStrings or:[(eachLine notNil and:[eachLine isString not])].
-        ]
+	aCollectionOfLines do:[:eachLine |
+	    includesNonStrings := includesNonStrings or:[(eachLine notNil and:[eachLine isString not])].
+	]
     ].
 
     widthOfWidestLine := nil. "/ i.e. unknown
     self textChanged.
 
     shown ifTrue:[
-        lastShown := self lastLineShown.
-        ((index-1) <= lastShown) ifTrue:[
-            index <= 2 ifTrue:[
-                self invalidate
-            ] ifFalse:[
-                index-1 to:lastShown do:[:eachLine |
-                    self invalidateLine:eachLine
-                ].
-                "/  self redrawFromLine:index-1.
-            ].
-        ].
+	lastShown := self lastLineShown.
+	((index-1) <= lastShown) ifTrue:[
+	    index <= 2 ifTrue:[
+		self invalidate
+	    ] ifFalse:[
+		index-1 to:lastShown do:[:eachLine |
+		    self invalidateLine:eachLine
+		].
+		"/  self redrawFromLine:index-1.
+	    ].
+	].
     ].
     self contentsChanged.             "recompute scrollbars"
 
     (scrollWhenUpdating == #end or:[scrollWhenUpdating == #endOfText]) ifTrue:[
-        "/ self selection isNil ifTrue:[
-            self scrollToBottom.
-        "/ ]
+	"/ self selection isNil ifTrue:[
+	    self scrollToBottom.
+	"/ ]
     ].
 !
 
@@ -576,12 +576,12 @@
     self withoutRedrawAt:index put:aString.
 
     shown ifTrue:[
-        fontHeightBefore ~= fontHeight ifTrue:[
-            "/ must redraw everything
-            self invalidate.
-            ^ self
-        ].
-        self redrawLine:index.
+	fontHeightBefore ~= fontHeight ifTrue:[
+	    "/ must redraw everything
+	    self invalidate.
+	    ^ self
+	].
+	self redrawLine:index.
 
 "/ the code below is wrong - we really have to redraw everything, if the
 "/ fontHeight changes (due to a labelAndIcon in the list).
@@ -599,16 +599,16 @@
 "/            self redrawLine:index
 "/        ].
 
-        "/ asynchronous:
+	"/ asynchronous:
 "/        visibleLine := self listLineToVisibleLine:index.
 "/        visibleLine notNil ifTrue:[
 "/            y := self yOfVisibleLine:visibleLine.
 "/            self invalidate:((margin @ y) extent:(width@fontHeight))
 "/        ].
 
-        widthBefore ~~ widthOfWidestLine ifTrue:[
-            self contentsChanged
-        ]
+	widthBefore ~~ widthOfWidestLine ifTrue:[
+	    self contentsChanged
+	]
     ]
 
     "Modified: / 26.7.1998 / 13:36:33 / cg"
@@ -636,12 +636,12 @@
     |line|
 
     list notNil ifTrue:[
-        line := self listAt:lineNr.
-        line notNil ifTrue:[
-            (line size >= colNr) ifTrue:[
-                ^ line at:colNr
-            ]
-        ]
+	line := self listAt:lineNr.
+	line notNil ifTrue:[
+	    (line size >= colNr) ifTrue:[
+		^ line at:colNr
+	    ]
+	]
     ].
     ^ Character space
 
@@ -666,9 +666,9 @@
 
     l := something.
     l notNil ifTrue:[
-        l isString ifTrue:[
-            l := l asStringCollection
-        ]
+	l isString ifTrue:[
+	    l := l asStringCollection
+	]
     ].
     self list:l
 
@@ -743,7 +743,7 @@
      (remembered to optimize later redraws)."
 
     self
-        list:aCollection expandTabs:expand scanForNonStrings:scan includesNonStrings:true
+	list:aCollection expandTabs:expand scanForNonStrings:scan includesNonStrings:true
 
     "Modified: 5.6.1997 / 12:40:35 / cg"
 !
@@ -865,14 +865,14 @@
 
     ((startLineNr <= self lastLineShown)
     and:[endLineNr >= firstLineShown]) ifTrue:[
-        startLineNr to:self lastLineShown do:[:eachLine |
-            self invalidateLine:eachLine
-        ].
+	startLineNr to:self lastLineShown do:[:eachLine |
+	    self invalidateLine:eachLine
+	].
     ].
 
     nLines := list size.
     (firstLineShown >= nLines) ifTrue:[
-        self makeLineVisible:nLines
+	self makeLineVisible:nLines
     ].
     self contentsChanged.
 !
@@ -891,34 +891,34 @@
     shown ifFalse:[^ self].
     visLine := self listLineToVisibleLine:lineNr.
     visLine notNil ifTrue:[
-        w := self widthForScrollBetween:lineNr and:(firstLineShown + nLinesShown).
+	w := self widthForScrollBetween:lineNr and:(firstLineShown + nLinesShown).
 "/        x := textStartLeft.
 "/ CLAUS fixes leftOver selection pixels
-        w := w + leftMargin.
-        x := margin.
-
-        srcY := topMargin + (visLine * fontHeight).
+	w := w + leftMargin.
+	x := margin.
+
+	srcY := topMargin + (visLine * fontHeight).
 "/        h := ((nLinesShown - visLine) * fontHeight).
-        h := (height - margin - srcY).
-        h > 0 ifTrue:[
-            self catchExpose.
-            self 
-                copyFrom:self 
-                x:x y:srcY
-                toX:x y:(srcY - fontHeight)
-                width:w height:h
-                async:true.
-        ].
-        self redrawVisibleLine:nFullLinesShown.
-        "
-         redraw last partial line - if any
-        "
-        (nFullLinesShown ~~ nLinesShown) ifTrue:[
-            self redrawVisibleLine:nLinesShown
-        ].
-        h > 0 ifTrue:[
-            self waitForExpose
-        ].
+	h := (height - margin - srcY).
+	h > 0 ifTrue:[
+	    self catchExpose.
+	    self 
+		copyFrom:self 
+		x:x y:srcY
+		toX:x y:(srcY - fontHeight)
+		width:w height:h
+		async:true.
+	].
+	self redrawVisibleLine:nFullLinesShown.
+	"
+	 redraw last partial line - if any
+	"
+	(nFullLinesShown ~~ nLinesShown) ifTrue:[
+	    self redrawVisibleLine:nLinesShown
+	].
+	h > 0 ifTrue:[
+	    self waitForExpose
+	].
     ]
 
     "Modified: / 27.2.1998 / 12:36:59 / cg"
@@ -933,7 +933,7 @@
     list removeIndex:lineNr.
 
     lineNr < firstLineShown ifTrue:[
-        firstLineShown := firstLineShown - 1
+	firstLineShown := firstLineShown - 1
     ].
     self contentsChanged.
     ^ true
@@ -949,7 +949,7 @@
 
     ((startLineNr <= self lastLineShown)
     and:[endLineNr >= firstLineShown]) ifTrue:[
-        self invalidate.
+	self invalidate.
     ].
 
     self contentsChanged.
@@ -967,9 +967,9 @@
     oldSize := self size.
     l := something.
     l notNil ifTrue:[
-        l isString ifTrue:[
-            l := l asStringCollection
-        ]
+	l isString ifTrue:[
+	    l := l asStringCollection
+	]
     ].
     self setList:l.
 
@@ -1005,8 +1005,8 @@
     |oldFirst nonStringsBefore linesShownBefore|
 
     (aCollection isNil and:[list isNil]) ifTrue:[
-        "no change"
-        ^ self
+	"no change"
+	^ self
     ].
 
 "/    list isNil ifTrue:[
@@ -1022,41 +1022,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 := 0 @ viewOrigin y.
+	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
@@ -1102,16 +1102,16 @@
 
     len := col2 - col1 + 1.
     list notNil ifTrue:[
-        line := self listAt:lineNr.
-        line notNil ifTrue:[
-            (line size >= col1) ifTrue:[
-                s := line copyFrom:col1.
-                s size < len ifTrue:[
-                    ^ s paddedTo:len
-                ].
-                ^ s copyTo:len
-            ]
-        ]
+	line := self listAt:lineNr.
+	line notNil ifTrue:[
+	    (line size >= col1) ifTrue:[
+		s := line copyFrom:col1.
+		s size < len ifTrue:[
+		    ^ s paddedTo:len
+		].
+		^ s copyTo:len
+	    ]
+	]
     ].
     ^ String new:len withAll:Character space
 
@@ -1138,10 +1138,10 @@
     |text sz index last|
 
     (startLine == endLine) ifTrue:[
-        "part of a line"
-        ^ StringCollection with:(self listAt:startLine
-                                        from:startCol
-                                          to:endCol)
+	"part of a line"
+	^ StringCollection with:(self listAt:startLine
+					from:startCol
+					  to:endCol)
     ].
     sz := endLine - startLine + 1.
     text := StringCollection new:sz.
@@ -1149,17 +1149,17 @@
     "get 1st and last (possibly) partial lines"
     text at:1 put:(self listAt:startLine from:startCol).
     endCol == 0 ifTrue:[
-        last := ''
+	last := ''
     ] ifFalse:[
-        last := self listAt:endLine to:endCol.
+	last := self listAt:endLine to:endCol.
     ].
     text at:sz put:last.
 
     "get bulk of text"
     index := 2.
     (startLine + 1) to:(endLine - 1) do:[:lineNr |
-        text at:index put:(self listAt:lineNr).
-        index := index + 1
+	text at:index put:(self listAt:lineNr).
+	index := index + 1
     ].
     ^ text
 
@@ -1179,25 +1179,25 @@
     oldLine := self listAt:index.
     list at:index put:aString.
     oldLine ~= aString ifTrue:[
-        self textChanged
+	self textChanged
     ].
 
     didIncludeNonStrings := includesNonStrings.
     includesNonStrings ifFalse:[
-        includesNonStrings := (aString notNil and:[aString isString not]).
+	includesNonStrings := (aString notNil and:[aString isString not]).
     ] ifTrue:[
-        (aString isNil or:[aString isString]) ifTrue:[
-            includesNonStrings := (list findFirst:[:l | l notNil and:[l isString not]]) ~~ 0.
-        ]
+	(aString isNil or:[aString isString]) ifTrue:[
+	    includesNonStrings := (list findFirst:[:l | l notNil and:[l isString not]]) ~~ 0.
+	]
     ].
 
     includesNonStrings ~~ didIncludeNonStrings ifTrue:[
-        self getFontParameters.
-        self computeNumberOfLinesShown
+	self getFontParameters.
+	self computeNumberOfLinesShown
     ].
 
     widthOfWidestLine notNil ifTrue:[
-        self recomputeWidthOfWidestLineFor:aString
+	self recomputeWidthOfWidestLineFor:aString
     ].
 
     "Modified: / 26.7.1998 / 13:00:14 / cg"
@@ -1208,14 +1208,14 @@
 
     list isNil ifTrue:[list := OrderedCollection new].
     aCollectionOfLines do:[:eachLine |
-        list addAll:aCollectionOfLines beforeIndex:index.
+	list addAll:aCollectionOfLines beforeIndex:index.
     ].
 
     widthOfWidestLine := nil. "/ i.e. unknown
     self textChanged.
 
     ((index-1) <= self lastLineShown) ifTrue:[
-        self redrawFromLine:index-1.
+	self redrawFromLine:index-1.
     ].
 
     self contentsChanged.             "recompute scrollbars"
@@ -1233,11 +1233,11 @@
     "set the background color of the contents"
 
     bgColor ~~ aColor ifTrue:[
-        bgColor := aColor.
-        self viewBackground:bgColor.
-        shown ifTrue:[
-            self invalidate "/ clear; redraw
-        ]
+	bgColor := aColor.
+	self viewBackground:bgColor.
+	shown ifTrue:[
+	    self invalidate "/ clear; redraw
+	]
     ]
 
     "Modified: 3.5.1997 / 10:27:40 / cg"
@@ -1247,28 +1247,28 @@
     "set the font for all shown text.
      Redraws everything.
      CAVEAT: with the addition of Text objects,
-             this method is going to be obsoleted by a textStyle
-             method, which allows specific control over
-             normalFont/boldFont/italicFont parameters."
+	     this method is going to be obsoleted by a textStyle
+	     method, which allows specific control over
+	     normalFont/boldFont/italicFont parameters."
 
     aFont isNil ifTrue:[
-        ^ self error:'nil font' mayProceed:true
+	^ self error:'nil font' mayProceed:true
     ].
     font ~~ aFont ifTrue:[
-        super font:(aFont onDevice:device).
-        preferredExtent := nil.
-        widthOfWidestLine := nil. "/ i.e. unknown
-        self getFontParameters.
-        realized ifTrue:[
-            (font graphicsDevice == device) ifTrue:[
-                self getFontParameters.
-                self computeNumberOfLinesShown.
-                shown ifTrue:[
-                    self redrawFromVisibleLine:1 to:nLinesShown
-                ]
-            ].
-            self contentsChanged
-        ]
+	super font:(aFont onDevice:device).
+	preferredExtent := nil.
+	widthOfWidestLine := nil. "/ i.e. unknown
+	self getFontParameters.
+	realized ifTrue:[
+	    (font graphicsDevice == device) ifTrue:[
+		self getFontParameters.
+		self computeNumberOfLinesShown.
+		shown ifTrue:[
+		    self redrawFromVisibleLine:1 to:nLinesShown
+		]
+	    ].
+	    self contentsChanged
+	]
     ]
 
     "Modified: 5.7.1996 / 17:55:34 / cg"
@@ -1279,7 +1279,7 @@
      by which lines are vertically separated."
 
     fontHeight ~~ pixels ifTrue:[
-        fontHeight := pixels.
+	fontHeight := pixels.
     ]
 
     "Created: 17.4.1997 / 01:41:33 / cg"
@@ -1295,10 +1295,10 @@
     "set the foreground color"
 
     fgColor ~~ aColor ifTrue:[
-        fgColor := aColor.
-        shown ifTrue:[
-            self invalidate 
-        ]
+	fgColor := aColor.
+	shown ifTrue:[
+	    self invalidate 
+	]
     ]
 
     "Modified: 29.5.1996 / 16:19:02 / cg"
@@ -1308,11 +1308,11 @@
     "set both foreground and background colors"
 
     ((fgColor ~~ color1) or:[bgColor ~~ color2]) ifTrue:[
-        fgColor := color1.
-        bgColor := color2.
-        shown ifTrue:[
-            self invalidate 
-        ]
+	fgColor := color1.
+	bgColor := color2.
+	shown ifTrue:[
+	    self invalidate 
+	]
     ]
 
     "Modified: 29.5.1996 / 16:19:05 / cg"
@@ -1357,12 +1357,12 @@
     |newMargin|
 
     aNumber ~~ level ifTrue:[
-        newMargin := aNumber abs.
-        textStartLeft := leftMargin + newMargin.
-        textStartTop := topMargin + newMargin.
-        innerWidth := width - textStartLeft - newMargin.
-
-        super level:aNumber.
+	newMargin := aNumber abs.
+	textStartLeft := leftMargin + newMargin.
+	textStartTop := topMargin + newMargin.
+	innerWidth := width - textStartLeft - newMargin.
+
+	super level:aNumber.
     ]
 
     "Modified: 11.8.1997 / 02:59:15 / cg"
@@ -1373,8 +1373,8 @@
      by which lines are vertically separated."
 
     lineSpacing ~~ pixels ifTrue:[
-        lineSpacing := pixels.
-        self getFontParameters.
+	lineSpacing := pixels.
+	self getFontParameters.
     ]
 
     "Modified: 22.5.1996 / 12:22:29 / cg"
@@ -1455,7 +1455,7 @@
     "ST-80 compatibility"
 
     aspectSymbol notNil ifTrue:[aspectMsg := aspectSymbol. 
-                             listMsg isNil ifTrue:[listMsg := aspectSymbol]].
+			     listMsg isNil ifTrue:[listMsg := aspectSymbol]].
     listSymbol notNil ifTrue:[listMsg := listSymbol].
     changeSymbol notNil ifTrue:[changeMsg := changeSymbol].
     menuMsg := menuSymbol.
@@ -1488,35 +1488,35 @@
     |idx|
 
     changedObject == model ifTrue:[
-        model isList ifTrue:[
-            list ~~ model ifTrue:[
-                something == #at: ifTrue:[
-                    idx := aParameter isCollection ifTrue:[aParameter at:1]
-                                                  ifFalse:[aParameter].
-                    ^ self at:aParameter put:(model at:idx).
-                ].
-                something == #insert: ifTrue:[
-                    (list size + 1) >= aParameter ifTrue:[
-                        ^ self add:(model at:aParameter) beforeIndex:aParameter
-                    ].
-                ].
-                something == #remove: ifTrue:[
-                    list size >= aParameter ifTrue:[
-                        ^ self removeIndex:aParameter
-                    ]
-                ].
-            ].
-            ^ self getListFromModel.
-        ].
-
-        (aspectMsg notNil
-        and:[something == aspectMsg]) ifTrue:[
-            ^ self getListFromModel.
-        ].
-
-        something == #size ifTrue:[
-            ^ self getListFromModelScroll:false.
-        ]
+	model isList ifTrue:[
+	    list ~~ model ifTrue:[
+		something == #at: ifTrue:[
+		    idx := aParameter isCollection ifTrue:[aParameter at:1]
+						  ifFalse:[aParameter].
+		    ^ self at:aParameter put:(model at:idx).
+		].
+		something == #insert: ifTrue:[
+		    (list size + 1) >= aParameter ifTrue:[
+			^ self add:(model at:aParameter) beforeIndex:aParameter
+		    ].
+		].
+		something == #remove: ifTrue:[
+		    list size >= aParameter ifTrue:[
+			^ self removeIndex:aParameter
+		    ]
+		].
+	    ].
+	    ^ self getListFromModel.
+	].
+
+	(aspectMsg notNil
+	and:[something == aspectMsg]) ifTrue:[
+	    ^ self getListFromModel.
+	].
+
+	something == #size ifTrue:[
+	    ^ self getListFromModelScroll:false.
+	]
     ].
     ^ super update:something with:aParameter from:changedObject
 
@@ -1538,11 +1538,11 @@
     sH := lineSpacing // 2.
 
     backgroundAlreadyClearedColor == bg ifFalse:[
-        self paint:bg.
-        self fillRectangleX:margin 
-                          y:y-sH
-                      width:(width - (margin * 2))
-                     height:(endVisLineNr - startVisLineNr + 1) * fontHeight + (lineSpacing - sH).
+	self paint:bg.
+	self fillRectangleX:margin 
+			  y:y-sH
+		      width:(width - (margin * 2))
+		     height:(endVisLineNr - startVisLineNr + 1) * fontHeight + (lineSpacing - sH).
     ].
     list isNil ifTrue:[^ self].
 
@@ -1552,28 +1552,28 @@
     startLine := startVisLineNr + firstLineShown - 1.
     endLine := endVisLineNr + firstLineShown - 1.
     (startLine == 0) ifTrue:[
-        y := y + fontHeight.
-        startLine := startLine + 1
+	y := y + fontHeight.
+	startLine := startLine + 1
     ].
 
     (endLine > listSize) ifTrue:[
-        e := listSize
+	e := listSize
     ] ifFalse:[
-        e := endLine
+	e := endLine
     ].
 
     (startLine <= e) ifTrue:[
-        x := textStartLeft - viewOrigin x.
-        self paint:fg on:bg.
-        self from:startLine to:e do:[:line |
-            line notNil ifTrue:[
-                "/ remove lines color emphasis, to enforce color.
-                "/ otherwise blue text is not visible if selection-bg is blue
-                l := self withoutColorEmphasis:line ifFg:fg andBg:bg.
-                self displayOpaqueString:l x:x y:y
-            ].
-            y := y + fontHeight
-        ]
+	x := textStartLeft - viewOrigin x.
+	self paint:fg on:bg.
+	self from:startLine to:e do:[:line |
+	    line notNil ifTrue:[
+		"/ remove lines color emphasis, to enforce color.
+		"/ otherwise blue text is not visible if selection-bg is blue
+		l := self withoutColorEmphasis:line ifFg:fg andBg:bg.
+		self displayOpaqueString:l x:x y:y
+	    ].
+	    y := y + fontHeight
+	]
     ]
 
     "Modified: / 15.12.1999 / 23:19:39 / cg"
@@ -1588,23 +1588,23 @@
 
     y := self yOfVisibleLine:visLineNr.
     backgroundAlreadyClearedColor == bg ifFalse:[
-        self paint:bg.
-        self fillRectangleX:margin y:y - (lineSpacing//2)
-                      width:(width - (2 * margin)) 
-                     height:fontHeight.
+	self paint:bg.
+	self fillRectangleX:margin y:y - (lineSpacing//2)
+		      width:(width - (2 * margin)) 
+		     height:fontHeight.
     ].
     line notNil ifTrue:[
-        self paint:fg on:bg.
-
-        "/ remove lines color emphasis, to enforce color.
-        "/ otherwise blue text is not visible if selection-bg is blue.
-        "/ this is only done in EditTextViews and subClasses.
-        self suppressEmphasisInSelection ifFalse:[
-            l := line
-        ] ifTrue:[
-            l := self withoutColorEmphasis:line ifFg:fg andBg:bg.
-        ].
-        self displayOpaqueString:l x:x y:(y + fontAscent)
+	self paint:fg on:bg.
+
+	"/ remove lines color emphasis, to enforce color.
+	"/ otherwise blue text is not visible if selection-bg is blue.
+	"/ this is only done in EditTextViews and subClasses.
+	self suppressEmphasisInSelection ifFalse:[
+	    l := line
+	] ifTrue:[
+	    l := self withoutColorEmphasis:line ifFg:fg andBg:bg.
+	].
+	self displayOpaqueString:l x:x y:(y + fontAscent)
     ]
 
     "Modified: / 15.12.1999 / 23:19:46 / cg"
@@ -1619,12 +1619,12 @@
 
     y := self yOfVisibleLine:visLineNr.
     line notNil ifTrue:[
-        self paint:fg on:bg.
-
-        "/ remove lines color emphasis, to enforce color.
-        "/ otherwise blue text is not visible if selection-bg is blue
-        l := self withoutColorEmphasis:line ifFg:fg andBg:bg.
-        self displayOpaqueString:l x:x y:(y + fontAscent)
+	self paint:fg on:bg.
+
+	"/ remove lines color emphasis, to enforce color.
+	"/ otherwise blue text is not visible if selection-bg is blue
+	l := self withoutColorEmphasis:line ifFg:fg andBg:bg.
+	self displayOpaqueString:l x:x y:(y + fontAscent)
     ]
 
     "Modified: / 15.12.1999 / 23:19:55 / cg"
@@ -1633,19 +1633,26 @@
 drawLine:lineStringArg inVisible:visLineNr col:col with:fg and:bg
     "draw single character at col index of visible line in fg/bg"
 
-    |y yf x lineString characterString w|
+    |y yf x len lineString characterString w|
 
     lineString := lineStringArg.
-    (lineString notNil and:[lineString isString not]) ifTrue:[
-        ^ self drawVisibleLine:visLineNr with:fg and:bg
-    ].
+    len := lineString size.
 
     x := (self xOfCol:col inVisibleLine:visLineNr) - viewOrigin x.
     y := self yOfVisibleLine:visLineNr.
+    yf := y - (lineSpacing // 2).
+
+    (lineString notNil and:[lineString isString not]) ifTrue:[
+        w := lineString widthFrom:col to:(col min:len) on:self.
+        self clippedTo:(Rectangle origin:(x@yf) extent:(w@fontHeight)) do:[
+            self drawVisibleLine:visLineNr with:fg and:bg
+        ].
+        ^ self
+    ].
+
     self paint:bg.
 
-    yf := y - (lineSpacing // 2).
-    col > lineString size ifTrue:[
+    col > len ifTrue:[
         self fillRectangleX:x y:yf width:(font width) height:fontHeight.
         self paint:fg
     ] ifFalse:[
@@ -1812,11 +1819,11 @@
     "draw a visible line in fg/bg"
 
     self 
-        drawLine:(self visibleAt:visLineNr) 
-        atX:(textStartLeft - viewOrigin x) 
-        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"
 !
@@ -1826,7 +1833,7 @@
      the current paint (#redrawX:y:w:h).
     "
     backgroundAlreadyClearedColor ~~ paint ifTrue:[
-        super fillRectangleX:x y:y width:w height:h
+	super fillRectangleX:x y:y width:w height:h
     ]
 
 
@@ -1844,14 +1851,14 @@
  
     visLineNr := self listLineToVisibleLine:line.
     visLineNr notNil ifTrue:[
-        yTop := self yOfVisibleLine:visLineNr.
-        yTop isNil ifTrue:[^ self]. "/ not visible
-        (yTop + fontHeight) < 0 ifTrue:[^ self]. "/ not visible
-        self 
-            invalidateDeviceRectangle:(Rectangle 
-                            left:margin top:yTop 
-                            width:(width - (2 * margin)) height:fontHeight)
-            repairNow:false.
+	yTop := self yOfVisibleLine:visLineNr.
+	yTop isNil ifTrue:[^ self]. "/ not visible
+	(yTop + fontHeight) < 0 ifTrue:[^ self]. "/ not visible
+	self 
+	    invalidateDeviceRectangle:(Rectangle 
+			    left:margin top:yTop 
+			    width:(width - (2 * margin)) height:fontHeight)
+	    repairNow:false.
     ]
 
     "Created: / 5.3.1998 / 01:24:19 / cg"
@@ -1866,24 +1873,24 @@
     |listSize newOrigin|
 
     shown ifTrue:[
-        list notNil ifTrue:[
-            listSize := self numberOfLines.
-
-            listSize == 0 ifTrue:[
-                widthOfWidestLine := 0.
-            ].
+	list notNil ifTrue:[
+	    listSize := self numberOfLines.
+
+	    listSize == 0 ifTrue:[
+		widthOfWidestLine := 0.
+	    ].
         
-            "
-             if we are beyond the end, scroll up a bit
-            "
-            ((firstLineShown + nFullLinesShown) > listSize) ifTrue:[
-                newOrigin := listSize - nFullLinesShown + 1.
-                newOrigin < 1 ifTrue:[
-                    newOrigin := 1
-                ].
-                self scrollToLine: newOrigin.
-            ].
-        ].
+	    "
+	     if we are beyond the end, scroll up a bit
+	    "
+	    ((firstLineShown + nFullLinesShown) > listSize) ifTrue:[
+		newOrigin := listSize - nFullLinesShown + 1.
+		newOrigin < 1 ifTrue:[
+		    newOrigin := 1
+		].
+		self scrollToLine: newOrigin.
+	    ].
+	].
     ].
 
     ^ super contentsChanged
@@ -1896,8 +1903,8 @@
     "a key was pressed - handle page-keys here"
 
     <resource: #keyboard (#PreviousPage #NextPage #HalfPageUp #HalfPageDown
-                          #BeginOfText #EndOfText
-                          #ScrollUp #ScrollDown )>
+			  #BeginOfText #EndOfText
+			  #ScrollUp #ScrollDown )>
     |sensor n|
 
     (key == #PreviousPage) ifTrue: [^ self pageUp].
@@ -1910,20 +1917,20 @@
 
     sensor := self sensor.
     (key == #ScrollUp) ifTrue:[
-        sensor isNil ifTrue:[
-            n := 1
-        ] ifFalse:[
-            n := 1 + (sensor compressKeyPressEventsWithKey:#ScrollUp).
-        ].
-        ^ self scrollUp:n
+	sensor isNil ifTrue:[
+	    n := 1
+	] ifFalse:[
+	    n := 1 + (sensor compressKeyPressEventsWithKey:#ScrollUp).
+	].
+	^ self scrollUp:n
     ].
     (key == #ScrollDown) ifTrue:[
-        sensor isNil ifTrue:[
-            n := 1
-        ] ifFalse:[
-            n := 1 + (sensor compressKeyPressEventsWithKey:#ScrollDown).
-        ].
-        ^ self scrollDown:n
+	sensor isNil ifTrue:[
+	    n := 1
+	] ifFalse:[
+	    n := 1 + (sensor compressKeyPressEventsWithKey:#ScrollDown).
+	].
+	^ self scrollDown:n
     ].
 
     super keyPress:key x:x y:y
@@ -1954,40 +1961,40 @@
     backgroundAlreadyClearedColor := bgColor.
 
     (includesNonStrings or:[w > (width // 4 * 3)]) ifTrue:[
-        "includes non strings or area is big enough redraw whole lines"
-        self redrawFromVisibleLine:startLine to:stopLine
+	"includes non strings or area is big enough redraw whole lines"
+	self redrawFromVisibleLine:startLine to:stopLine
     ] ifFalse:[
-        line := self visibleAt:startLine.
-
-        (fontIsFixedWidth and:[line isMemberOf:String]) ifFalse:[
-            "start/end col has to be computed for each line"
-
-            startLine to:stopLine do:[:i |
-                startCol := self colOfX:x inVisibleLine:i.
-                endCol := self colOfX:(x + w) inVisibleLine:i.
-                startCol > 0 ifTrue:[
-                    endCol > 0 ifTrue:[
-                        self redrawVisibleLine:i from:startCol to:endCol
-                    ]
-                ]
-            ]
-        ] ifTrue:[
-            "start/end col is the same for all lines"
-            startCol := self colOfX:x inVisibleLine:startLine.
-            endCol := self colOfX:(x + w) inVisibleLine:startLine.
-            startCol > 0 ifTrue:[
-                endCol > 0 ifTrue:[
-                    startLine to:stopLine do:[:i |
-                        line := self visibleAt:i.
-                        (line isMemberOf:String) ifTrue:[
-                            self redrawVisibleLine:i from:startCol to:endCol
-                        ] ifFalse:[
-                            self redrawVisibleLine:i
-                        ]
-                    ]
-                ]
-            ]
-        ]
+	line := self visibleAt:startLine.
+
+	(fontIsFixedWidth and:[line isMemberOf:String]) ifFalse:[
+	    "start/end col has to be computed for each line"
+
+	    startLine to:stopLine do:[:i |
+		startCol := self colOfX:x inVisibleLine:i.
+		endCol := self colOfX:(x + w) inVisibleLine:i.
+		startCol > 0 ifTrue:[
+		    endCol > 0 ifTrue:[
+			self redrawVisibleLine:i from:startCol to:endCol
+		    ]
+		]
+	    ]
+	] ifTrue:[
+	    "start/end col is the same for all lines"
+	    startCol := self colOfX:x inVisibleLine:startLine.
+	    endCol := self colOfX:(x + w) inVisibleLine:startLine.
+	    startCol > 0 ifTrue:[
+		endCol > 0 ifTrue:[
+		    startLine to:stopLine do:[:i |
+			line := self visibleAt:i.
+			(line isMemberOf:String) ifTrue:[
+			    self redrawVisibleLine:i from:startCol to:endCol
+			] ifFalse:[
+			    self redrawVisibleLine:i
+			]
+		    ]
+		]
+	    ]
+	]
     ].
     backgroundAlreadyClearedColor := nil.
     self clippingRectangle:saveClip.
@@ -2066,13 +2073,13 @@
 
     n := DefaultTopMargin.
     n isInteger ifFalse:[
-        n := (self verticalPixelPerMillimeter:n) rounded.
+	n := (self verticalPixelPerMillimeter:n) rounded.
     ].
     self topMargin:n.
 
     n := DefaultLeftMargin.
     n isInteger ifFalse:[
-        n := (self verticalPixelPerMillimeter:n) rounded.
+	n := (self verticalPixelPerMillimeter:n) rounded.
     ].
     self leftMargin:n.
 
@@ -2109,14 +2116,14 @@
     |sz|
 
     self extentChangedFlag ifTrue:[
-        self computeNumberOfLinesShown.
+	self computeNumberOfLinesShown.
     ].
 
     firstLineShown ~~ 1 ifTrue:[
-        sz := self size.
-        firstLineShown + nLinesShown > sz ifTrue:[
-            self scrollToLine:sz - nLinesShown.
-        ]
+	sz := self size.
+	firstLineShown + nLinesShown > sz ifTrue:[
+	    self scrollToLine:sz - nLinesShown.
+	]
     ].
 
     super realize.
@@ -2147,13 +2154,13 @@
 
     n := DefaultTopMargin.
     n isInteger ifFalse:[
-        n := (self verticalPixelPerMillimeter:n) rounded.
+	n := (self verticalPixelPerMillimeter:n) rounded.
     ].
     self topMargin:n.
 
     n := DefaultLeftMargin.
     n isInteger ifFalse:[
-        n := (self verticalPixelPerMillimeter:n) rounded.
+	n := (self verticalPixelPerMillimeter:n) rounded.
     ].
     self leftMargin:n.
 
@@ -2186,11 +2193,11 @@
     self checkForExistingLine:lineNr.
     pos := 1.
     1 to:(lineNr - 1) do:[:lnr |
-        lineString := self at:lnr.
-        lineString notNil ifTrue:[
-            pos := pos + lineString size
-        ].
-        pos := pos + 1   "the return-character"
+	lineString := self at:lnr.
+	lineString notNil ifTrue:[
+	    pos := pos + lineString size
+	].
+	pos := pos + 1   "the return-character"
     ].
     ^ pos + col - 1
 
@@ -2200,13 +2207,13 @@
     "check if a line for lineNr exists; if not, expand text"
 
     list isNil ifTrue: [
-        list := StringCollection new:lineNr.
-        self contentsChanged
+	list := StringCollection new:lineNr.
+	self contentsChanged
     ] ifFalse: [
-        lineNr > (list size) ifTrue:[
-            self grow:lineNr.
-            self contentsChanged
-        ]
+	lineNr > (list size) ifTrue:[
+	    self grow:lineNr.
+	    self contentsChanged
+	]
     ]
 !
 
@@ -2335,9 +2342,9 @@
     nLinesShown := nFullLinesShown.
 
     partialLines ifTrue:[
-        ((nLinesShown * fontHeight) < innerHeight) ifTrue:[
-            nLinesShown := nLinesShown + 1
-        ]
+	((nLinesShown * fontHeight) < innerHeight) ifTrue:[
+	    nLinesShown := nLinesShown + 1
+	]
     ]
 
     "Modified: 29.5.1996 / 14:48:43 / cg"
@@ -2356,38 +2363,38 @@
 
     newLine := ''.
     aList do:[:line |
-        ((line size == 0) or:[line isBlank]) ifTrue:[
-            newList add:newLine.
-            newLine := ''
-        ] ifFalse:[
-            special := ((line at:1) == ${) or:[(line includes:$\)].
-            special := special or:[(line at:1) == $}].
-            special ifFalse:[
-                newList add:(newLine , line)
-            ] ifTrue:[
-                charIndex := 1.
-                [charIndex <= line size] whileTrue:[
-                    char := line at:charIndex.
-                    ((char == ${ ) or:[char == $} ]) ifTrue:[
-                        "left-brace: ignore rest of line"
-                        charIndex := line size + 1
-                    ] ifFalse:[
-                        (char == $\) ifTrue:[
-                            inEscape := true
-                        ] ifFalse:[
-                            inEscape ifTrue:[
-                                (char == Character space) ifTrue:[
-                                    inEscape := false
-                                ]
-                            ] ifFalse:[
-                                newLine := newLine copyWith:char
-                            ]
-                        ].
-                        charIndex := charIndex + 1
-                    ]
-                ]
-            ]
-        ]
+	((line size == 0) or:[line isBlank]) ifTrue:[
+	    newList add:newLine.
+	    newLine := ''
+	] ifFalse:[
+	    special := ((line at:1) == ${) or:[(line includes:$\)].
+	    special := special or:[(line at:1) == $}].
+	    special ifFalse:[
+		newList add:(newLine , line)
+	    ] ifTrue:[
+		charIndex := 1.
+		[charIndex <= line size] whileTrue:[
+		    char := line at:charIndex.
+		    ((char == ${ ) or:[char == $} ]) ifTrue:[
+			"left-brace: ignore rest of line"
+			charIndex := line size + 1
+		    ] ifFalse:[
+			(char == $\) ifTrue:[
+			    inEscape := true
+			] ifFalse:[
+			    inEscape ifTrue:[
+				(char == Character space) ifTrue:[
+				    inEscape := false
+				]
+			    ] ifFalse:[
+				newLine := newLine copyWith:char
+			    ]
+			].
+			charIndex := charIndex + 1
+		    ]
+		]
+	    ]
+	]
     ].
     ^ newList
 
@@ -2407,20 +2414,20 @@
     hMax := font height.
 
     includesNonStrings == true ifTrue:[
-        "/
-        "/ find maximum height of lines
-        "/
-        hMax := list inject:hMax into:[:maxSoFar :thisLine | 
-                                        thisLine isNil ifTrue:[
-                                            maxSoFar
-                                        ] ifFalse:[
-                                            (thisLine isMemberOf:String) ifTrue:[
-                                                maxSoFar
-                                            ] ifFalse:[   
-                                                maxSoFar max:(thisLine heightOn:self)
-                                            ]
-                                        ]
-                              ].
+	"/
+	"/ find maximum height of lines
+	"/
+	hMax := list inject:hMax into:[:maxSoFar :thisLine | 
+					thisLine isNil ifTrue:[
+					    maxSoFar
+					] ifFalse:[
+					    (thisLine isMemberOf:String) ifTrue:[
+						maxSoFar
+					    ] ifFalse:[   
+						maxSoFar max:(thisLine heightOn:self)
+					    ]
+					]
+			      ].
 
     ].
     fontHeight := hMax + lineSpacing.
@@ -2438,23 +2445,23 @@
     |text msg|
 
     model notNil ifTrue:[
-        msg := listMsg.
-        msg isNil ifTrue:[
-            msg := aspectMsg
-        ].
-
-
-        msg notNil ifTrue:[
-            text := model perform:msg.
-            text notNil ifTrue:[
-                text := text asStringCollection.
-            ].
+	msg := listMsg.
+	msg isNil ifTrue:[
+	    msg := aspectMsg
+	].
+
+
+	msg notNil ifTrue:[
+	    text := model perform:msg.
+	    text notNil ifTrue:[
+		text := text asStringCollection.
+	    ].
 "/ SV: this does not work, if model uses (i.e. updates) the same stringCollection
 "/ as the view!!
 "/            text ~= list ifTrue:[
-                self list:text
+		self list:text
 "/            ].
-        ].
+	].
     ].
 
     "Modified: 26.4.1996 / 14:09:42 / cg"
@@ -2468,26 +2475,26 @@
     |text msg|
 
     model notNil ifTrue:[
-        msg := listMsg.
-        msg isNil ifTrue:[
-            msg := aspectMsg
-        ].
-
-        msg notNil ifTrue:[
-            text := model perform:msg.
-            text notNil ifTrue:[
-                text := text asStringCollection.
-            ].
+	msg := listMsg.
+	msg isNil ifTrue:[
+	    msg := aspectMsg
+	].
+
+	msg notNil ifTrue:[
+	    text := model perform:msg.
+	    text notNil ifTrue:[
+		text := text asStringCollection.
+	    ].
 "/ SV: this does not work, if model uses (i.e. updates) the same stringCollection
 "/ as the view!!
 "/            text ~= list ifTrue:[
-                aBoolean ifTrue:[
-                    self list:text
-                ] ifFalse:[
-                    self setList:text
-                ]
+		aBoolean ifTrue:[
+		    self list:text
+		] ifFalse:[
+		    self setList:text
+		]
 "/            ].
-        ].
+	].
     ].
 
     "Modified: 19.2.1997 / 12:08:50 / stefan"
@@ -2514,11 +2521,11 @@
     sum := 0.
     lastLine := self size.
     [(sum < charPos) and:[lineNr <= lastLine]] whileTrue:[
-        sum := sum + (self at:lineNr) size + 1.
-        lineNr := lineNr + 1
+	sum := sum + (self at:lineNr) size + 1.
+	lineNr := lineNr + 1
     ].
     sum == charPos ifTrue:[
-        ^ lineNr
+	^ lineNr
     ].
 
     ^ lineNr - 1
@@ -2608,16 +2615,16 @@
     |w|
 
     widthOfWidestLine notNil ifTrue:[
-        aString isString ifTrue:[
-            w := font widthOf:aString
-        ] ifFalse:[
-            w := aString widthOn:self
-        ].
-        w > widthOfWidestLine ifTrue:[
-            widthOfWidestLine := w.
-        ] ifFalse:[
-            widthOfWidestLine := nil "/ means: unknown
-        ].
+	aString isString ifTrue:[
+	    w := font widthOf:aString
+	] ifFalse:[
+	    w := aString widthOn:self
+	].
+	w > widthOfWidestLine ifTrue:[
+	    widthOfWidestLine := w.
+	] ifFalse:[
+	    widthOfWidestLine := nil "/ means: unknown
+	].
     ].
     ^ widthOfWidestLine
 !
@@ -2642,9 +2649,9 @@
     listLineNr := visibleLineNr + firstLineShown - 1.
     (listLineNr == 0) ifTrue:[^ nil].
     (list notNil) ifTrue:[
-        listsize := self size
+	listsize := self size
     ] ifFalse:[
-        listsize := 0
+	listsize := 0
     ].
     (listLineNr <= listsize) ifTrue:[^ self at:listLineNr].
     ^ ''
@@ -2725,7 +2732,7 @@
 
     entry isNil ifTrue:[^ 0].
     entry isString ifTrue:[
-        ^ font widthOf:entry
+	^ font widthOf:entry
     ].
     ^ entry widthOn:self
 
@@ -2743,11 +2750,11 @@
      listSize "{ Class: SmallInteger }" |
 
     includesNonStrings ifTrue:[
-        ^ width
+	^ width
     ].
 
     fontIsFixedWidth ifTrue:[
-        ^ (self lengthOfLongestLineBetween:firstLine and:lastLine) * fontWidth
+	^ (self lengthOfLongestLineBetween:firstLine and:lastLine) * fontWidth
     ].
     listSize := self size.
     max := 0.
@@ -2756,16 +2763,16 @@
 
     (first > listSize) ifTrue:[^ max].
     (last > listSize) ifTrue:[
-        last := listSize
+	last := listSize
     ].
 
     self from:first to:last do:[:line |
-        line notNil ifTrue:[
-            thisLen := font widthOf:line.
-            (thisLen > max) ifTrue:[
-                max := thisLen
-            ]
-        ]
+	line notNil ifTrue:[
+	    thisLen := font widthOf:line.
+	    (thisLen > max) ifTrue:[
+		max := thisLen
+	    ]
+	]
     ].
     ^ max
 !
@@ -2903,11 +2910,11 @@
     font := font onDevice:device.
     ^ numLines * fontHeight 
 "/                            + textStartTop
-                            - (lineSpacing // 2)
-                            + (font descent)
+			    - (lineSpacing // 2)
+			    + (font descent)
 "/                            + (font descent)       
 "/                            + (font descent * 2) "makes it look better"
-                                .
+				.
 
 "/    "it used to be that code - which is wrong"
 "/    (nLinesShown == nFullLinesShown) ifTrue:[
@@ -2939,9 +2946,9 @@
 
     lineString := self listAt:lineNr.
     lineString notNil ifTrue:[
-        indent := lineString leftIndent.
-        indent == lineString size ifTrue:[^ 0].
-        ^ indent.
+	indent := lineString leftIndent.
+	indent == lineString size ifTrue:[^ 0].
+	^ indent.
     ].
     ^ 0
 
@@ -2972,15 +2979,15 @@
 
     (first > listSize) ifTrue:[^ max].
     (last > listSize) ifTrue:[
-        last := listSize
+	last := listSize
     ].
     self from:first to:last do:[:lineString |
-        lineString notNil ifTrue:[
-            thisLen := lineString size.
-            (thisLen > max) ifTrue:[
-                max := thisLen
-            ]
-        ]
+	lineString notNil ifTrue:[
+	    thisLen := lineString size.
+	    (thisLen > max) ifTrue:[
+		max := thisLen
+	    ]
+	]
     ].
     ^ max
 
@@ -3027,59 +3034,59 @@
     widthOfWidestLine notNil ifTrue:[^ widthOfWidestLine + (leftMargin * 2)].
 
     (d := device) isNil ifTrue:[
-        "/ mhmh - really dont know yet
-        d := Screen current
+	"/ mhmh - really dont know yet
+	d := Screen current
     ].
     f := font := font onDevice:d.
 
     includesNonStrings ifTrue:[
-        max := list 
-                   inject:0 
-                   into:[:maxSoFar :entry |
-                             (
-                                 entry isNil ifTrue:[
-                                     0
-                                 ] ifFalse:[
-                                    entry isString ifTrue:[
-                                        f widthOf:entry
-                                    ] ifFalse:[
-                                        entry widthOn:self
-                                    ]
-                                 ]
-                             ) max:maxSoFar.
-                        ]
+	max := list 
+		   inject:0 
+		   into:[:maxSoFar :entry |
+			     (
+				 entry isNil ifTrue:[
+				     0
+				 ] ifFalse:[
+				    entry isString ifTrue:[
+					f widthOf:entry
+				    ] ifFalse:[
+					entry widthOn:self
+				    ]
+				 ]
+			     ) max:maxSoFar.
+			]
     ] ifFalse:[
-        fontIsFixedWidth ifTrue:[
-            max := lengthOfLongestString := 0.
-            list notNil ifTrue:[
-                list do:[:line |
-                    line notNil ifTrue:[
-                        (line isString and:[line hasChangeOfEmphasis not]) ifTrue:[
-                            line size > lengthOfLongestString ifTrue:[
-                                lengthOfLongestString := line size
-                            ].
-                        ] ifFalse:[
-                            max := max max:(line widthOn:self)
-                        ]
-                    ]
-                ].
-                max := max max:(lengthOfLongestString * fontWidth)
-            ].
-        ] ifFalse:[
-            false "fontIsFixedWidth" ifTrue:[
-                max := self lengthOfLongestLine * fontWidth
-            ] ifFalse:[
-                max := 0.
-                list notNil ifTrue:[
-                    list do:[:line |
-                        line notNil ifTrue:[
-                            max := max max:(line widthOn:self)
-                        ]
-                    ].
+	fontIsFixedWidth ifTrue:[
+	    max := lengthOfLongestString := 0.
+	    list notNil ifTrue:[
+		list do:[:line |
+		    line notNil ifTrue:[
+			(line isString and:[line hasChangeOfEmphasis not]) ifTrue:[
+			    line size > lengthOfLongestString ifTrue:[
+				lengthOfLongestString := line size
+			    ].
+			] ifFalse:[
+			    max := max max:(line widthOn:self)
+			]
+		    ]
+		].
+		max := max max:(lengthOfLongestString * fontWidth)
+	    ].
+	] ifFalse:[
+	    false "fontIsFixedWidth" ifTrue:[
+		max := self lengthOfLongestLine * fontWidth
+	    ] ifFalse:[
+		max := 0.
+		list notNil ifTrue:[
+		    list do:[:line |
+			line notNil ifTrue:[
+			    max := max max:(line widthOn:self)
+			]
+		    ].
     "/                max := max max:(f widthOf:list)
-                ].
-            ].
-        ].
+		].
+	    ].
+	].
     ].
     widthOfWidestLine := max.
     ^ max + (leftMargin * 2)
@@ -3098,13 +3105,13 @@
     list isNil ifTrue:[^ 0].
 
     (d := device) isNil ifTrue:[
-        "/ mhmh - really dont know yet
-        d := Screen current
+	"/ mhmh - really dont know yet
+	d := Screen current
     ].
     f := font := font onDevice:d.
 
     line isString ifTrue:[
-        ^ f widthOf:line
+	^ f widthOf:line
     ].
     ^ line widthOn:self
 
@@ -3146,7 +3153,7 @@
     "redraw complete view"
 
     shown ifTrue:[
-        self redrawFromVisibleLine:1 to:nLinesShown
+	self redrawFromVisibleLine:1 to:nLinesShown
     ]
 !
 
@@ -3156,17 +3163,17 @@
     |visibleLine first|
 
     shown ifTrue:[
-        "if first line to redraw is above 1st visible line,
-         start redraw at 1st visible line"
-        (lineNr < firstLineShown) ifTrue:[
-            first := firstLineShown
-        ] ifFalse:[
-            first := lineNr
-        ].
-        visibleLine := self listLineToVisibleLine:first.
-        visibleLine notNil ifTrue:[
-            self redrawFromVisibleLine:visibleLine to:nLinesShown
-        ]
+	"if first line to redraw is above 1st visible line,
+	 start redraw at 1st visible line"
+	(lineNr < firstLineShown) ifTrue:[
+	    first := firstLineShown
+	] ifFalse:[
+	    first := lineNr
+	].
+	visibleLine := self listLineToVisibleLine:first.
+	visibleLine notNil ifTrue:[
+	    self redrawFromVisibleLine:visibleLine to:nLinesShown
+	]
     ]
 !
 
@@ -3176,28 +3183,28 @@
     |visibleFirst visibleLast first last lastLineShown|
 
     shown ifTrue:[
-        lastLineShown := firstLineShown + nLinesShown - 1.
-        (start <= lastLineShown) ifTrue:[
-            (end >= firstLineShown) ifTrue:[
-
-                "if first line to redraw is above 1st visible line,
-                 start redraw at 1st visible line"
-
-                (start < firstLineShown) ifTrue:[
-                    first := firstLineShown
-                ] ifFalse:[
-                    first := start
-                ].
-                (end > lastLineShown) ifTrue:[
-                    last := lastLineShown
-                ] ifFalse:[
-                    last := end
-                ].
-                visibleFirst := self listLineToVisibleLine:first.
-                visibleLast := self listLineToVisibleLine:last.
-                self redrawFromVisibleLine:visibleFirst to:visibleLast
-            ]
-        ]
+	lastLineShown := firstLineShown + nLinesShown - 1.
+	(start <= lastLineShown) ifTrue:[
+	    (end >= firstLineShown) ifTrue:[
+
+		"if first line to redraw is above 1st visible line,
+		 start redraw at 1st visible line"
+
+		(start < firstLineShown) ifTrue:[
+		    first := firstLineShown
+		] ifFalse:[
+		    first := start
+		].
+		(end > lastLineShown) ifTrue:[
+		    last := lastLineShown
+		] ifFalse:[
+		    last := end
+		].
+		visibleFirst := self listLineToVisibleLine:first.
+		visibleLast := self listLineToVisibleLine:last.
+		self redrawFromVisibleLine:visibleFirst to:visibleLast
+	    ]
+	]
     ]
 !
 
@@ -3205,7 +3212,7 @@
     "redraw a visible line range"
 
     shown ifTrue:[
-        self drawFromVisibleLine:startVisLineNr to:endVisLineNr with:fgColor and:bgColor
+	self drawFromVisibleLine:startVisLineNr to:endVisLineNr with:fgColor and:bgColor
     ]
 !
 
@@ -3230,7 +3237,7 @@
 
     visibleLine := self listLineToVisibleLine:lineNr.
     visibleLine notNil ifTrue:[
-        self redrawVisibleLine:visibleLine
+	self redrawVisibleLine:visibleLine
     ]
 !
 
@@ -3241,7 +3248,7 @@
 
     visibleLine := self listLineToVisibleLine:lineNr.
     visibleLine notNil ifTrue:[
-        self redrawVisibleLine:visibleLine col:col
+	self redrawVisibleLine:visibleLine col:col
     ]
 !
 
@@ -3252,7 +3259,7 @@
 
     visibleLine := self listLineToVisibleLine:lineNr.
     visibleLine notNil ifTrue:[
-        self redrawVisibleLine:visibleLine from:startCol
+	self redrawVisibleLine:visibleLine from:startCol
     ]
 !
 
@@ -3263,7 +3270,7 @@
 
     visibleLine := self listLineToVisibleLine:lineNr.
     visibleLine notNil ifTrue:[
-        self redrawVisibleLine:visibleLine from:startCol to:endCol
+	self redrawVisibleLine:visibleLine from:startCol to:endCol
     ]
 !
 
@@ -3271,7 +3278,7 @@
     "redraw a visible line"
 
     shown ifTrue:[
-        self drawVisibleLine:visLineNr with:fgColor and:bgColor
+	self drawVisibleLine:visLineNr with:fgColor and:bgColor
     ]
 !
 
@@ -3279,7 +3286,7 @@
     "redraw single character at col index of visible line"
 
     shown ifTrue:[
-        self drawVisibleLine:visLineNr col:col with:fgColor and:bgColor
+	self drawVisibleLine:visLineNr col:col with:fgColor and:bgColor
     ]
 !
 
@@ -3287,7 +3294,7 @@
     "redraw right part of a visible line from startCol to end of line"
 
     shown ifTrue:[
-        self drawVisibleLine:visLineNr from:startCol with:fgColor and:bgColor
+	self drawVisibleLine:visLineNr from:startCol with:fgColor and:bgColor
     ]
 !
 
@@ -3295,7 +3302,11 @@
     "redraw part of a visible line"
 
     shown ifTrue:[
-        self drawVisibleLine:visLineNr from:startCol to:endCol with:fgColor and:bgColor
+        startCol == endCol ifTrue:[
+            self redrawVisibleLine:visLineNr col:startCol
+        ] ifFalse:[
+            self drawVisibleLine:visLineNr from:startCol to:endCol with:fgColor and:bgColor
+        ]
     ]
 ! !
 
@@ -3383,27 +3394,27 @@
 "/    ].
 
     (self needScrollToMakeLineVisible:aListLineNr) ifFalse:[
-        ^ self
+	^ self
     ].
 
     (aListLineNr < nFullLinesShown) ifTrue:[
-        "/ at the very top of the list - show from top
-        newTopLine := 1
+	"/ at the very top of the list - show from top
+	newTopLine := 1
     ] ifFalse:[
-        (nFullLinesShown < 3) ifTrue:[
-            "/ a small view - show from that line
-            newTopLine := aListLineNr
-        ] ifFalse:[
-            bott := self numberOfLines - (nFullLinesShown - 1).
-            (aListLineNr > bott) ifTrue:[
-                "/ at the end of the list - show the bottom of the list
-                newTopLine := bott
-            ] ifFalse:[
-                "/ somewhere else - place selected line into the middle of
-                "/ the view
-                newTopLine := (aListLineNr - (nFullLinesShown // 2) + 1)
-            ]
-        ]
+	(nFullLinesShown < 3) ifTrue:[
+	    "/ a small view - show from that line
+	    newTopLine := aListLineNr
+	] ifFalse:[
+	    bott := self numberOfLines - (nFullLinesShown - 1).
+	    (aListLineNr > bott) ifTrue:[
+		"/ at the end of the list - show the bottom of the list
+		newTopLine := bott
+	    ] ifFalse:[
+		"/ somewhere else - place selected line into the middle of
+		"/ the view
+		newTopLine := (aListLineNr - (nFullLinesShown // 2) + 1)
+	    ]
+	]
     ].
 
     self scrollToLine:newTopLine.
@@ -3419,10 +3430,10 @@
     |index list|
 
     (list := self list) notNil ifTrue:[
-        index := list indexOf:someString.
-        index ~~ 0 ifTrue:[
-            self makeLineVisible:index
-        ]
+	index := list indexOf:someString.
+	index ~~ 0 ifTrue:[
+	    self makeLineVisible:index
+	]
     ]
 
     "Modified: 9.9.1997 / 10:10:13 / cg"
@@ -3433,9 +3444,9 @@
      Numbering starts with 1 for the very first line of the text."
 
     (aListLineNr >= firstLineShown) ifTrue:[
-        (aListLineNr < (firstLineShown + nFullLinesShown)) ifTrue:[
-            ^ false
-        ]
+	(aListLineNr < (firstLineShown + nFullLinesShown)) ifTrue:[
+	    ^ false
+	]
     ].
     ^ true
 
@@ -3448,9 +3459,9 @@
      Numbering starts with 1 for the very first line of the text."
 
     (aListLineNr >= firstLineShown) ifTrue:[
-        (aListLineNr < (firstLineShown + nFullLinesShown)) ifTrue:[
-            ^ false
-        ]
+	(aListLineNr < (firstLineShown + nFullLinesShown)) ifTrue:[
+	    ^ false
+	]
     ].
     ^ true
 
@@ -3479,8 +3490,8 @@
     "change origin to scroll down some lines (towards the bottom of the text)"
 
     nLines ~~ 0 ifTrue:[
-        self scrollTo:(viewOrigin + (0 @ (fontHeight * nLines)))
-               redraw:true
+	self scrollTo:(viewOrigin + (0 @ (fontHeight * nLines)))
+	       redraw:true
     ]
 
     "Modified: / 21.5.1999 / 15:59:52 / cg"
@@ -3492,7 +3503,7 @@
      THIS WILL VANISH!!"
 
     pix > 0 ifTrue:[
-        self scrollTo:(viewOrigin + (0 @ (pix abs))) redraw:true
+	self scrollTo:(viewOrigin + (0 @ (pix abs))) redraw:true
     ]
 
 
@@ -3505,7 +3516,7 @@
 
     nPixel := aPixelOffset - viewOrigin x.
     nPixel ~~ 0 ifTrue:[
-        self scrollTo:(viewOrigin + (nPixel @ 0)) redraw:true
+	self scrollTo:(viewOrigin + (nPixel @ 0)) redraw:true
     ]
 
     "Modified: / 3.3.1999 / 22:55:20 / cg"
@@ -3515,7 +3526,7 @@
     "change origin to scroll left some cols"
 
     nPixel ~~ 0 ifTrue:[
-        self scrollTo:(viewOrigin - (nPixel @ 0)) redraw:true
+	self scrollTo:(viewOrigin - (nPixel @ 0)) redraw:true
     ]
 
     "Modified: / 21.5.1999 / 15:59:16 / cg"
@@ -3525,7 +3536,7 @@
     "change origin to scroll right some cols"
 
     nPixel ~~ 0 ifTrue:[
-        self scrollTo:(self viewOrigin + (nPixel @ 0)) redraw:true
+	self scrollTo:(self viewOrigin + (nPixel @ 0)) redraw:true
     ]
 
     "Modified: / 21.5.1999 / 15:59:21 / cg"
@@ -3560,20 +3571,20 @@
     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)
+	]
     ]
 !
 
@@ -3581,7 +3592,7 @@
     "change origin to start (left) of text"
 
     viewOrigin x ~~ 0 ifTrue:[
-        self scrollToCol:1
+	self scrollToCol:1
     ]
 !
 
@@ -3589,11 +3600,11 @@
     "change origin to make aLineNr be the top line"
 
     aLineNr < firstLineShown ifTrue:[
-        self scrollUp:(firstLineShown - aLineNr)
+	self scrollUp:(firstLineShown - aLineNr)
     ] ifFalse:[
-        aLineNr > firstLineShown ifTrue:[
-            self scrollDown:(aLineNr - firstLineShown)
-        ]
+	aLineNr > firstLineShown ifTrue:[
+	    self scrollDown:(aLineNr - firstLineShown)
+	]
     ]
 !
 
@@ -3616,8 +3627,8 @@
     "change origin to scroll up some lines (towards the top of the text)"
 
     nLines ~~ 0 ifTrue:[
-        self scrollTo:(viewOrigin - (0 @ (fontHeight * nLines)))
-               redraw:true
+	self scrollTo:(viewOrigin - (0 @ (fontHeight * nLines)))
+	       redraw:true
     ]
 
     "Modified: / 21.5.1999 / 15:59:45 / cg"
@@ -3629,7 +3640,7 @@
     THIS WILL VANISH!!"
 
     pix > 0 ifTrue:[
-        self scrollTo:(viewOrigin - (0 @ pix)) redraw:true
+	self scrollTo:(viewOrigin - (0 @ pix)) redraw:true
     ]
 
 
@@ -3645,7 +3656,7 @@
     "/ kludge for last partial line
     "/
     nFullLinesShown ~~ nLinesShown ifTrue:[
-        nL := nL + 1
+	nL := nL + 1
     ].
     lineNr := (((nL * percent) asFloat / 100.0) + 0.5) asInteger + 1.
     self scrollToLine:lineNr
@@ -3663,11 +3674,11 @@
     deltaT := 0.5 / mm.
 
     (deltaT = autoScrollDeltaT) ifFalse:[
-        autoScrollDeltaT := deltaT.
-        autoScrollBlock isNil ifTrue:[
-            autoScrollBlock := [self realized ifTrue:[self scrollSelectDown]].
-            Processor addTimedBlock:autoScrollBlock afterSeconds:deltaT
-        ]
+	autoScrollDeltaT := deltaT.
+	autoScrollBlock isNil ifTrue:[
+	    autoScrollBlock := [self realized ifTrue:[self scrollSelectDown]].
+	    Processor addTimedBlock:autoScrollBlock afterSeconds:deltaT
+	]
     ]
 !
 
@@ -3683,11 +3694,11 @@
     deltaT := 0.5 / mm.
 
     (deltaT = autoScrollDeltaT) ifFalse:[
-        autoScrollDeltaT := deltaT.
-        autoScrollBlock isNil ifTrue:[
-            autoScrollBlock := [ self realized ifTrue:[self scrollSelectLeft]].
-            Processor addTimedBlock:autoScrollBlock afterSeconds:deltaT
-        ]
+	autoScrollDeltaT := deltaT.
+	autoScrollBlock isNil ifTrue:[
+	    autoScrollBlock := [ self realized ifTrue:[self scrollSelectLeft]].
+	    Processor addTimedBlock:autoScrollBlock afterSeconds:deltaT
+	]
     ]
 !
 
@@ -3703,11 +3714,11 @@
     deltaT := 0.5 / mm.
 
     (deltaT = autoScrollDeltaT) ifFalse:[
-        autoScrollDeltaT := deltaT.
-        autoScrollBlock isNil ifTrue:[
-            autoScrollBlock := [self realized ifTrue:[self scrollSelectRight]].
-            Processor addTimedBlock:autoScrollBlock afterSeconds:deltaT
-        ]
+	autoScrollDeltaT := deltaT.
+	autoScrollBlock isNil ifTrue:[
+	    autoScrollBlock := [self realized ifTrue:[self scrollSelectRight]].
+	    Processor addTimedBlock:autoScrollBlock afterSeconds:deltaT
+	]
     ]
 !
 
@@ -3723,11 +3734,11 @@
     deltaT := 0.5 / mm.
 
     (deltaT = autoScrollDeltaT) ifFalse:[
-        autoScrollDeltaT := deltaT.
-        autoScrollBlock isNil ifTrue:[
-            autoScrollBlock := [self realized ifTrue:[self scrollSelectUp]].
-            Processor addTimedBlock:autoScrollBlock afterSeconds:deltaT
-        ]
+	autoScrollDeltaT := deltaT.
+	autoScrollBlock isNil ifTrue:[
+	    autoScrollBlock := [self realized ifTrue:[self scrollSelectUp]].
+	    Processor addTimedBlock:autoScrollBlock afterSeconds:deltaT
+	]
     ]
 !
 
@@ -3735,10 +3746,10 @@
     "stop any auto-scroll"
 
     autoScrollBlock notNil ifTrue:[
-        self compressMotionEvents:true.
-        Processor removeTimedBlock:autoScrollBlock.
-        autoScrollBlock := nil.
-        autoScrollDeltaT := nil
+	self compressMotionEvents:true.
+	Processor removeTimedBlock:autoScrollBlock.
+	autoScrollBlock := nil.
+	autoScrollDeltaT := nil
     ].
 !
 
@@ -3965,28 +3976,28 @@
 
     "is this acharacter within a word ?"
     (wordCheck value:thisCharacter) ifTrue:[
-        [wordCheck value:thisCharacter] whileTrue:[
-            beginCol := beginCol - 1.
-            beginCol < 1 ifTrue:[
-                thisCharacter := Character space
-            ] ifFalse:[
-                thisCharacter := self characterAtLine:selectLine col:beginCol
-            ]
-        ].
-        beginCol := beginCol + 1.
+	[wordCheck value:thisCharacter] whileTrue:[
+	    beginCol := beginCol - 1.
+	    beginCol < 1 ifTrue:[
+		thisCharacter := Character space
+	    ] ifFalse:[
+		thisCharacter := self characterAtLine:selectLine col:beginCol
+	    ]
+	].
+	beginCol := beginCol + 1.
     ] ifFalse:[
-        "nope - maybe its a space"
-        thisCharacter == Character space ifTrue:[
-            [beginCol > 1 and:[thisCharacter == Character space]] whileTrue:[
-                beginCol := beginCol - 1.
-                thisCharacter := self characterAtLine:selectLine col:beginCol
-            ].
-            thisCharacter ~~ Character space ifTrue:[
-                beginCol := beginCol + 1.
-            ].
-        ] ifFalse:[
-            "select single character"
-        ]
+	"nope - maybe its a space"
+	thisCharacter == Character space ifTrue:[
+	    [beginCol > 1 and:[thisCharacter == Character space]] whileTrue:[
+		beginCol := beginCol - 1.
+		thisCharacter := self characterAtLine:selectLine col:beginCol
+	    ].
+	    thisCharacter ~~ Character space ifTrue:[
+		beginCol := beginCol + 1.
+	    ].
+	] ifFalse:[
+	    "select single character"
+	]
     ].
     ^ beginCol
 !
@@ -4007,30 +4018,30 @@
 
     "is this acharacter within a word ?"
     (wordCheck value:thisCharacter) ifTrue:[
-        thisCharacter := self characterAtLine:selectLine col:endCol.
-        [wordCheck value:thisCharacter] whileTrue:[
-            endCol := endCol + 1.
-            thisCharacter := self characterAtLine:selectLine col:endCol
-        ].
-        endCol := endCol - 1.
+	thisCharacter := self characterAtLine:selectLine col:endCol.
+	[wordCheck value:thisCharacter] whileTrue:[
+	    endCol := endCol + 1.
+	    thisCharacter := self characterAtLine:selectLine col:endCol
+	].
+	endCol := endCol - 1.
     ] ifFalse:[
-        "nope - maybe its a space"
-        thisCharacter == Character space ifTrue:[
-            len := (self listAt:selectLine) size.
-            endCol > len ifTrue:[
-                "select rest to end"
-                endCol := 0
-            ] ifFalse:[
-                thisCharacter := self characterAtLine:selectLine col:endCol.
-                [endCol <= len and:[thisCharacter == Character space]] whileTrue:[
-                    endCol := endCol + 1.
-                    thisCharacter := self characterAtLine:selectLine col:endCol
-                ].
-                endCol := endCol - 1.
-            ]
-        ] ifFalse:[
-            "select single character"
-        ]
+	"nope - maybe its a space"
+	thisCharacter == Character space ifTrue:[
+	    len := (self listAt:selectLine) size.
+	    endCol > len ifTrue:[
+		"select rest to end"
+		endCol := 0
+	    ] ifFalse:[
+		thisCharacter := self characterAtLine:selectLine col:endCol.
+		[endCol <= len and:[thisCharacter == Character space]] whileTrue:[
+		    endCol := endCol + 1.
+		    thisCharacter := self characterAtLine:selectLine col:endCol
+		].
+		endCol := endCol - 1.
+	    ]
+	] ifFalse:[
+	    "select single character"
+	]
     ].
     ^ endCol.
 !
@@ -4122,11 +4133,11 @@
      Sorry, but pattern is no regular expression pattern (yet)"
 
     ^ self
-        searchBackwardFor:pattern 
-        ignoreCase:false 
-        startingAtLine:startLine col:startCol 
-        ifFound:block1 
-        ifAbsent:block2
+	searchBackwardFor:pattern 
+	ignoreCase:false 
+	startingAtLine:startLine col:startCol 
+	ifFound:block1 
+	ifAbsent:block2
 
     "Modified: 13.9.1997 / 01:07:36 / cg"
 !
@@ -4142,68 +4153,68 @@
 
     patternSize := pattern size.
     (list notNil and:[patternSize ~~ 0]) ifTrue:[
-        self withCursor:Cursor questionMark do:[
-
-            col := startCol + 1.
-            line1 := startLine.
-            line2 := list size.
-
-            pattern includesUnescapedMatchCharacters ifTrue:[
-                p := pattern species new:0.
-                (pattern startsWith:$*) ifFalse:[
-                    p := p , '*'
-                ].
-                p := p , pattern.
-                (pattern endsWith:$*) ifFalse:[
-                    p := p , '*'
-                ].
-                realPattern := pattern.
-                (realPattern startsWith:$*) ifTrue:[
-                    realPattern := realPattern copyFrom:2
-                ].
-                line1 to:line2 do:[:lnr |
-                    lineString := list at:lnr.
-                    lineString notNil ifTrue:[
-                        "/ first a crude check ...
-                        (p match:lineString ignoreCase:ignCase) ifTrue:[
-                            "/ ok, there it is; look at which position
-                            col := lineString 
-                                        findMatchString:realPattern 
-                                        startingAt:col 
-                                        ignoreCase:ignCase 
-                                        ifAbsent:0.
-                            col ~~ 0 ifTrue:[
-                                ^ block1 value:lnr value:col.
-                            ]
-                        ].
-                    ].
-                    col := 1
-                ]
-            ] ifFalse:[
-                p := pattern withoutMatchEscapes.
-                line1 to:line2 do:[:lnr |
-                    lineString := list at:lnr.
-                    lineString isString ifTrue:[
-                        ignCase ifTrue:[
-                            col := lineString 
-                                        findMatchString:p 
-                                        startingAt:col 
-                                        ignoreCase:ignCase 
-                                        ifAbsent:0.
-                        ] ifFalse:[
-                            col := lineString 
-                                        findString:p 
-                                        startingAt:col 
-                                        ifAbsent:0.
-                        ].
-                        col ~~ 0 ifTrue:[
-                            ^ block1 value:lnr value:col.
-                        ]
-                    ].
-                    col := 1
-                ]
-            ].
-        ]
+	self withCursor:Cursor questionMark do:[
+
+	    col := startCol + 1.
+	    line1 := startLine.
+	    line2 := list size.
+
+	    pattern includesUnescapedMatchCharacters ifTrue:[
+		p := pattern species new:0.
+		(pattern startsWith:$*) ifFalse:[
+		    p := p , '*'
+		].
+		p := p , pattern.
+		(pattern endsWith:$*) ifFalse:[
+		    p := p , '*'
+		].
+		realPattern := pattern.
+		(realPattern startsWith:$*) ifTrue:[
+		    realPattern := realPattern copyFrom:2
+		].
+		line1 to:line2 do:[:lnr |
+		    lineString := list at:lnr.
+		    lineString notNil ifTrue:[
+			"/ first a crude check ...
+			(p match:lineString ignoreCase:ignCase) ifTrue:[
+			    "/ ok, there it is; look at which position
+			    col := lineString 
+					findMatchString:realPattern 
+					startingAt:col 
+					ignoreCase:ignCase 
+					ifAbsent:0.
+			    col ~~ 0 ifTrue:[
+				^ block1 value:lnr value:col.
+			    ]
+			].
+		    ].
+		    col := 1
+		]
+	    ] ifFalse:[
+		p := pattern withoutMatchEscapes.
+		line1 to:line2 do:[:lnr |
+		    lineString := list at:lnr.
+		    lineString isString ifTrue:[
+			ignCase ifTrue:[
+			    col := lineString 
+					findMatchString:p 
+					startingAt:col 
+					ignoreCase:ignCase 
+					ifAbsent:0.
+			] ifFalse:[
+			    col := lineString 
+					findString:p 
+					startingAt:col 
+					ifAbsent:0.
+			].
+			col ~~ 0 ifTrue:[
+			    ^ block1 value:lnr value:col.
+			]
+		    ].
+		    col := 1
+		]
+	    ].
+	]
     ].
     "not found"
 
@@ -4218,11 +4229,11 @@
      found evaluate block2."
 
     ^ self
-        searchForwardFor:pattern 
-        ignoreCase:false 
-        startingAtLine:startLine col:startCol 
-        ifFound:block1 
-        ifAbsent:block2
+	searchForwardFor:pattern 
+	ignoreCase:false 
+	startingAtLine:startLine col:startCol 
+	ifFound:block1 
+	ifAbsent:block2
 
     "Modified: 13.9.1997 / 01:07:11 / cg"
 ! !
@@ -4238,20 +4249,20 @@
 
     includesNonStrings := false.
     list notNil ifTrue:[
-        nLines := self size.
-        1 to:nLines do:[:index |
-            line := self at:index.
-            line notNil ifTrue:[
-                line isString ifTrue:[
-                    newLine := line withTabsExpanded.
-                    newLine ~~ line ifTrue:[
-                        list at:index put:newLine
-                    ].
-                ] ifFalse:[
-                    includesNonStrings := true.
-                ]
-            ]
-        ]
+	nLines := self size.
+	1 to:nLines do:[:index |
+	    line := self at:index.
+	    line notNil ifTrue:[
+		line isString ifTrue:[
+		    newLine := line withTabsExpanded.
+		    newLine ~~ line ifTrue:[
+			list at:index put:newLine
+		    ].
+		] ifFalse:[
+		    includesNonStrings := true.
+		]
+	    ]
+	]
     ]
 
     "Modified: 30.8.1995 / 19:06:37 / claus"
@@ -4278,9 +4289,9 @@
     thisTab := tabPositions at:tabIndex.
     nTabs := tabPositions size.
     [thisTab <= col] whileTrue:[
-        (tabIndex == nTabs) ifTrue:[^ thisTab].
-        tabIndex := tabIndex + 1.
-        thisTab := tabPositions at:tabIndex
+	(tabIndex == nTabs) ifTrue:[^ thisTab].
+	tabIndex := tabIndex + 1.
+	thisTab := tabPositions at:tabIndex
     ].
     ^ thisTab
 !
@@ -4298,12 +4309,12 @@
     thisTab := tabPositions at:tabIndex.
     nTabs := tabPositions size.
     [thisTab < col] whileTrue:[
-        (tabIndex == nTabs) ifTrue:[^ thisTab].
-        tabIndex := tabIndex + 1.
-        thisTab := tabPositions at:tabIndex
+	(tabIndex == nTabs) ifTrue:[^ thisTab].
+	tabIndex := tabIndex + 1.
+	thisTab := tabPositions at:tabIndex
     ].
     (tabIndex == 1) ifTrue:[
-        ^ 1
+	^ 1
     ].
     ^ tabPositions at:(tabIndex - 1)
 !
@@ -4347,8 +4358,8 @@
     nTabs := 1.
     newLine := line copyFrom:9.
     [newLine startsWith:eightSpaces] whileTrue:[
-        newLine := newLine copyFrom:9.
-        nTabs := nTabs + 1.
+	newLine := newLine copyFrom:9.
+	nTabs := nTabs + 1.
     ].
     ^ (line species new:nTabs withAll:Character tab) asString , newLine.
 
@@ -4381,35 +4392,35 @@
     tmpString := line species new:currentMax.
     dstIndex := 1.
     line do:[:character |
-        (character == (Character tab)) ifTrue:[
-            nextTab := self nextTabAfter:dstIndex in:tabulatorTable.
-            [dstIndex < nextTab] whileTrue:[
-                tmpString at:dstIndex put:(Character space).
-                dstIndex := dstIndex + 1
-            ]
-        ] ifFalse:[
-            tmpString at:dstIndex put:character.
-            dstIndex := dstIndex + 1
-        ].
-        (dstIndex > currentMax) ifTrue:[
-            "
-             this cannot happen with <= 8 tabs
-            "
-            currentMax := currentMax + currentMax.
-            nString := line species new:currentMax.
-            nString replaceFrom:1 to:(dstIndex - 1) 
-                           with:tmpString startingAt:1.
-            tmpString := nString.
-            nString := nil
-        ].
-
-        "make stc-optimizer happy
-         - no need to return value of ifTrue:/ifFalse above"
-        0
+	(character == (Character tab)) ifTrue:[
+	    nextTab := self nextTabAfter:dstIndex in:tabulatorTable.
+	    [dstIndex < nextTab] whileTrue:[
+		tmpString at:dstIndex put:(Character space).
+		dstIndex := dstIndex + 1
+	    ]
+	] ifFalse:[
+	    tmpString at:dstIndex put:character.
+	    dstIndex := dstIndex + 1
+	].
+	(dstIndex > currentMax) ifTrue:[
+	    "
+	     this cannot happen with <= 8 tabs
+	    "
+	    currentMax := currentMax + currentMax.
+	    nString := line species new:currentMax.
+	    nString replaceFrom:1 to:(dstIndex - 1) 
+			   with:tmpString startingAt:1.
+	    tmpString := nString.
+	    nString := nil
+	].
+
+	"make stc-optimizer happy
+	 - no need to return value of ifTrue:/ifFalse above"
+	0
     ].
     dstIndex := dstIndex - 1.
     dstIndex == currentMax ifTrue:[
-        ^ tmpString
+	^ tmpString
     ].
     ^ tmpString copyTo:dstIndex
 
@@ -4427,5 +4438,5 @@
 !ListView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg/ListView.st,v 1.266 2002-07-23 19:35:54 mb Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg/ListView.st,v 1.267 2002-07-23 20:51:52 mb Exp $'
 ! !